diff options
author | Pierre Muller <muller@sourceware.org> | 2000-06-14 12:27:59 +0000 |
---|---|---|
committer | Pierre Muller <muller@sourceware.org> | 2000-06-14 12:27:59 +0000 |
commit | 373a8247302053107af695e14b869988b3395f79 (patch) | |
tree | c91e9c673f569c9634cfaa9c64ee7a7d2d569e78 /gdb | |
parent | c06ae4f232e6e2b3d3062ffc5bce2b4477cb388a (diff) | |
download | gdb-373a8247302053107af695e14b869988b3395f79.zip gdb-373a8247302053107af695e14b869988b3395f79.tar.gz gdb-373a8247302053107af695e14b869988b3395f79.tar.bz2 |
2000-06-14 Pierre Muller <muller@ics.u-strasbg.fr>
Add support for Pascal language. Part 1: new files.
* p-exp.y, p-lang.c, p-lang.h, p-typeprint.c, p-valprint.c: New files.
Diffstat (limited to 'gdb')
-rw-r--r-- | gdb/ChangeLog | 5 | ||||
-rw-r--r-- | gdb/p-exp.y | 1446 | ||||
-rw-r--r-- | gdb/p-lang.c | 430 | ||||
-rw-r--r-- | gdb/p-lang.h | 75 | ||||
-rw-r--r-- | gdb/p-typeprint.c | 882 | ||||
-rw-r--r-- | gdb/p-valprint.c | 1145 |
6 files changed, 3983 insertions, 0 deletions
diff --git a/gdb/ChangeLog b/gdb/ChangeLog index dff4b98..0360fa0 100644 --- a/gdb/ChangeLog +++ b/gdb/ChangeLog @@ -1,3 +1,8 @@ +2000-06-14 Pierre Muller <muller@ics.u-strasbg.fr> + + Add support for Pascal language. Part 1: new files. + * p-exp.y, p-lang.c, p-lang.h, p-typeprint.c, p-valprint.c: New files. + 2000-06-13 Kevin Buettner <kevinb@redhat.com> * ser-ocd.c, symtab.c: Eliminate use of PARAMS from these files. diff --git a/gdb/p-exp.y b/gdb/p-exp.y new file mode 100644 index 0000000..fa2aef0 --- /dev/null +++ b/gdb/p-exp.y @@ -0,0 +1,1446 @@ +/* YACC parser for Pascal expressions, for GDB. + Copyright (C) 2000 + Free Software Foundation, Inc. + +This file is part of GDB. + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */ + +/* This file is derived from c-exp.y */ + +/* Parse a Pascal expression from text in a string, + and return the result as a struct expression pointer. + That structure contains arithmetic operations in reverse polish, + with constants represented by operations that are followed by special data. + See expression.h for the details of the format. + What is important here is that it can be built up sequentially + during the process of parsing; the lower levels of the tree always + come first in the result. + + Note that malloc's and realloc's in this file are transformed to + xmalloc and xrealloc respectively by the same sed command in the + makefile that remaps any other malloc/realloc inserted by the parser + generator. Doing this with #defines and trying to control the interaction + with include files (<malloc.h> and <stdlib.h> for example) just became + too messy, particularly when such includes can be inserted at random + times by the parser generator. */ + +/* FIXME: there are still 21 shift/reduce conflicts + Other known bugs or limitations: + - pascal string operations are not supported at all. + - there are some problems with boolean types. + - Pascal type hexadecimal constants are not supported + because they conflict with the internal variables format. + Probably also lots of other problems, less well defined PM */ +%{ + +#include "defs.h" +#include "gdb_string.h" +#include <ctype.h> +#include "expression.h" +#include "value.h" +#include "parser-defs.h" +#include "language.h" +#include "p-lang.h" +#include "bfd.h" /* Required by objfiles.h. */ +#include "symfile.h" /* Required by objfiles.h. */ +#include "objfiles.h" /* For have_full_symbols and have_partial_symbols */ + +/* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc), + as well as gratuitiously global symbol names, so we can have multiple + yacc generated parsers in gdb. Note that these are only the variables + produced by yacc. If other parser generators (bison, byacc, etc) produce + additional global names that conflict at link time, then those parser + generators need to be fixed instead of adding those names to this list. */ + +#define yymaxdepth pascal_maxdepth +#define yyparse pascal_parse +#define yylex pascal_lex +#define yyerror pascal_error +#define yylval pascal_lval +#define yychar pascal_char +#define yydebug pascal_debug +#define yypact pascal_pact +#define yyr1 pascal_r1 +#define yyr2 pascal_r2 +#define yydef pascal_def +#define yychk pascal_chk +#define yypgo pascal_pgo +#define yyact pascal_act +#define yyexca pascal_exca +#define yyerrflag pascal_errflag +#define yynerrs pascal_nerrs +#define yyps pascal_ps +#define yypv pascal_pv +#define yys pascal_s +#define yy_yys pascal_yys +#define yystate pascal_state +#define yytmp pascal_tmp +#define yyv pascal_v +#define yy_yyv pascal_yyv +#define yyval pascal_val +#define yylloc pascal_lloc +#define yyreds pascal_reds /* With YYDEBUG defined */ +#define yytoks pascal_toks /* With YYDEBUG defined */ +#define yylhs pascal_yylhs +#define yylen pascal_yylen +#define yydefred pascal_yydefred +#define yydgoto pascal_yydgoto +#define yysindex pascal_yysindex +#define yyrindex pascal_yyrindex +#define yygindex pascal_yygindex +#define yytable pascal_yytable +#define yycheck pascal_yycheck + +#ifndef YYDEBUG +#define YYDEBUG 0 /* Default to no yydebug support */ +#endif + +int yyparse (void); + +static int yylex (void); + +void +yyerror (char *); + +static char * uptok (char *, int); +%} + +/* Although the yacc "value" of an expression is not used, + since the result is stored in the structure being created, + other node types do have values. */ + +%union + { + LONGEST lval; + struct { + LONGEST val; + struct type *type; + } typed_val_int; + struct { + DOUBLEST dval; + struct type *type; + } typed_val_float; + struct symbol *sym; + struct type *tval; + struct stoken sval; + struct ttype tsym; + struct symtoken ssym; + int voidval; + struct block *bval; + enum exp_opcode opcode; + struct internalvar *ivar; + + struct type **tvec; + int *ivec; + } + +%{ +/* YYSTYPE gets defined by %union */ +static int +parse_number (char *, int, int, YYSTYPE *); +%} + +%type <voidval> exp exp1 type_exp start variable qualified_name +%type <tval> type typebase +/* %type <bval> block */ + +/* Fancy type parsing. */ +%type <tval> ptype + +%token <typed_val_int> INT +%token <typed_val_float> FLOAT + +/* Both NAME and TYPENAME tokens represent symbols in the input, + and both convey their data as strings. + But a TYPENAME is a string that happens to be defined as a typedef + or builtin type name (such as int or char) + and a NAME is any other symbol. + Contexts where this distinction is not important can use the + nonterminal "name", which matches either NAME or TYPENAME. */ + +%token <sval> STRING +%token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */ +%token <tsym> TYPENAME +%type <sval> name +%type <ssym> name_not_typename + +/* A NAME_OR_INT is a symbol which is not known in the symbol table, + but which would parse as a valid number in the current input radix. + E.g. "c" when input_radix==16. Depending on the parse, it will be + turned into a name or into a number. */ + +%token <ssym> NAME_OR_INT + +%token STRUCT CLASS SIZEOF COLONCOLON +%token ERROR + +/* Special type cases, put in to allow the parser to distinguish different + legal basetypes. */ + +%token <voidval> VARIABLE + + +/* Object pascal */ +%token THIS +%token <lval> TRUE FALSE + +%left ',' +%left ABOVE_COMMA +%right ASSIGN +%left NOT +%left OR +%left XOR +%left ANDAND +%left '=' NOTEQUAL +%left '<' '>' LEQ GEQ +%left LSH RSH DIV MOD +%left '@' +%left '+' '-' +%left '*' '/' +%right UNARY INCREMENT DECREMENT +%right ARROW '.' '[' '(' +%token <ssym> BLOCKNAME +%type <bval> block +%left COLONCOLON + + +%% + +start : exp1 + | type_exp + ; + +type_exp: type + { write_exp_elt_opcode(OP_TYPE); + write_exp_elt_type($1); + write_exp_elt_opcode(OP_TYPE);} + ; + +/* Expressions, including the comma operator. */ +exp1 : exp + | exp1 ',' exp + { write_exp_elt_opcode (BINOP_COMMA); } + ; + +/* Expressions, not including the comma operator. */ +exp : exp '^' %prec UNARY + { write_exp_elt_opcode (UNOP_IND); } + +exp : '@' exp %prec UNARY + { write_exp_elt_opcode (UNOP_ADDR); } + +exp : '-' exp %prec UNARY + { write_exp_elt_opcode (UNOP_NEG); } + ; + +exp : NOT exp %prec UNARY + { write_exp_elt_opcode (UNOP_LOGICAL_NOT); } + ; + +exp : INCREMENT '(' exp ')' %prec UNARY + { write_exp_elt_opcode (UNOP_PREINCREMENT); } + ; + +exp : DECREMENT '(' exp ')' %prec UNARY + { write_exp_elt_opcode (UNOP_PREDECREMENT); } + ; + +exp : exp '.' name + { write_exp_elt_opcode (STRUCTOP_STRUCT); + write_exp_string ($3); + write_exp_elt_opcode (STRUCTOP_STRUCT); } + ; + +exp : exp '[' exp1 ']' + { write_exp_elt_opcode (BINOP_SUBSCRIPT); } + ; + +exp : exp '(' + /* This is to save the value of arglist_len + being accumulated by an outer function call. */ + { start_arglist (); } + arglist ')' %prec ARROW + { write_exp_elt_opcode (OP_FUNCALL); + write_exp_elt_longcst ((LONGEST) end_arglist ()); + write_exp_elt_opcode (OP_FUNCALL); } + ; + +arglist : + | exp + { arglist_len = 1; } + | arglist ',' exp %prec ABOVE_COMMA + { arglist_len++; } + ; + +exp : type '(' exp ')' %prec UNARY + { write_exp_elt_opcode (UNOP_CAST); + write_exp_elt_type ($1); + write_exp_elt_opcode (UNOP_CAST); } + ; + +exp : '(' exp1 ')' + { } + ; + +/* Binary operators in order of decreasing precedence. */ + +exp : exp '*' exp + { write_exp_elt_opcode (BINOP_MUL); } + ; + +exp : exp '/' exp + { write_exp_elt_opcode (BINOP_DIV); } + ; + +exp : exp DIV exp + { write_exp_elt_opcode (BINOP_INTDIV); } + ; + +exp : exp MOD exp + { write_exp_elt_opcode (BINOP_REM); } + ; + +exp : exp '+' exp + { write_exp_elt_opcode (BINOP_ADD); } + ; + +exp : exp '-' exp + { write_exp_elt_opcode (BINOP_SUB); } + ; + +exp : exp LSH exp + { write_exp_elt_opcode (BINOP_LSH); } + ; + +exp : exp RSH exp + { write_exp_elt_opcode (BINOP_RSH); } + ; + +exp : exp '=' exp + { write_exp_elt_opcode (BINOP_EQUAL); } + ; + +exp : exp NOTEQUAL exp + { write_exp_elt_opcode (BINOP_NOTEQUAL); } + ; + +exp : exp LEQ exp + { write_exp_elt_opcode (BINOP_LEQ); } + ; + +exp : exp GEQ exp + { write_exp_elt_opcode (BINOP_GEQ); } + ; + +exp : exp '<' exp + { write_exp_elt_opcode (BINOP_LESS); } + ; + +exp : exp '>' exp + { write_exp_elt_opcode (BINOP_GTR); } + ; + +exp : exp ANDAND exp + { write_exp_elt_opcode (BINOP_BITWISE_AND); } + ; + +exp : exp XOR exp + { write_exp_elt_opcode (BINOP_BITWISE_XOR); } + ; + +exp : exp OR exp + { write_exp_elt_opcode (BINOP_BITWISE_IOR); } + ; + +exp : exp ASSIGN exp + { write_exp_elt_opcode (BINOP_ASSIGN); } + ; + +exp : TRUE + { write_exp_elt_opcode (OP_BOOL); + write_exp_elt_longcst ((LONGEST) $1); + write_exp_elt_opcode (OP_BOOL); } + ; + +exp : FALSE + { write_exp_elt_opcode (OP_BOOL); + write_exp_elt_longcst ((LONGEST) $1); + write_exp_elt_opcode (OP_BOOL); } + ; + +exp : INT + { write_exp_elt_opcode (OP_LONG); + write_exp_elt_type ($1.type); + write_exp_elt_longcst ((LONGEST)($1.val)); + write_exp_elt_opcode (OP_LONG); } + ; + +exp : NAME_OR_INT + { YYSTYPE val; + parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val); + write_exp_elt_opcode (OP_LONG); + write_exp_elt_type (val.typed_val_int.type); + write_exp_elt_longcst ((LONGEST)val.typed_val_int.val); + write_exp_elt_opcode (OP_LONG); + } + ; + + +exp : FLOAT + { write_exp_elt_opcode (OP_DOUBLE); + write_exp_elt_type ($1.type); + write_exp_elt_dblcst ($1.dval); + write_exp_elt_opcode (OP_DOUBLE); } + ; + +exp : variable + ; + +exp : VARIABLE + /* Already written by write_dollar_variable. */ + ; + +exp : SIZEOF '(' type ')' %prec UNARY + { write_exp_elt_opcode (OP_LONG); + write_exp_elt_type (builtin_type_int); + CHECK_TYPEDEF ($3); + write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3)); + write_exp_elt_opcode (OP_LONG); } + ; + +exp : STRING + { /* C strings are converted into array constants with + an explicit null byte added at the end. Thus + the array upper bound is the string length. + There is no such thing in C as a completely empty + string. */ + char *sp = $1.ptr; int count = $1.length; + while (count-- > 0) + { + write_exp_elt_opcode (OP_LONG); + write_exp_elt_type (builtin_type_char); + write_exp_elt_longcst ((LONGEST)(*sp++)); + write_exp_elt_opcode (OP_LONG); + } + write_exp_elt_opcode (OP_LONG); + write_exp_elt_type (builtin_type_char); + write_exp_elt_longcst ((LONGEST)'\0'); + write_exp_elt_opcode (OP_LONG); + write_exp_elt_opcode (OP_ARRAY); + write_exp_elt_longcst ((LONGEST) 0); + write_exp_elt_longcst ((LONGEST) ($1.length)); + write_exp_elt_opcode (OP_ARRAY); } + ; + +/* Object pascal */ +exp : THIS + { write_exp_elt_opcode (OP_THIS); + write_exp_elt_opcode (OP_THIS); } + ; + +/* end of object pascal. */ + +block : BLOCKNAME + { + if ($1.sym != 0) + $$ = SYMBOL_BLOCK_VALUE ($1.sym); + else + { + struct symtab *tem = + lookup_symtab (copy_name ($1.stoken)); + if (tem) + $$ = BLOCKVECTOR_BLOCK (BLOCKVECTOR (tem), STATIC_BLOCK); + else + error ("No file or function \"%s\".", + copy_name ($1.stoken)); + } + } + ; + +block : block COLONCOLON name + { struct symbol *tem + = lookup_symbol (copy_name ($3), $1, + VAR_NAMESPACE, (int *) NULL, + (struct symtab **) NULL); + if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK) + error ("No function \"%s\" in specified context.", + copy_name ($3)); + $$ = SYMBOL_BLOCK_VALUE (tem); } + ; + +variable: block COLONCOLON name + { struct symbol *sym; + sym = lookup_symbol (copy_name ($3), $1, + VAR_NAMESPACE, (int *) NULL, + (struct symtab **) NULL); + if (sym == 0) + error ("No symbol \"%s\" in specified context.", + copy_name ($3)); + + write_exp_elt_opcode (OP_VAR_VALUE); + /* block_found is set by lookup_symbol. */ + write_exp_elt_block (block_found); + write_exp_elt_sym (sym); + write_exp_elt_opcode (OP_VAR_VALUE); } + ; + +qualified_name: typebase COLONCOLON name + { + struct type *type = $1; + if (TYPE_CODE (type) != TYPE_CODE_STRUCT + && TYPE_CODE (type) != TYPE_CODE_UNION) + error ("`%s' is not defined as an aggregate type.", + TYPE_NAME (type)); + + write_exp_elt_opcode (OP_SCOPE); + write_exp_elt_type (type); + write_exp_string ($3); + write_exp_elt_opcode (OP_SCOPE); + } + ; + +variable: qualified_name + | COLONCOLON name + { + char *name = copy_name ($2); + struct symbol *sym; + struct minimal_symbol *msymbol; + + sym = + lookup_symbol (name, (const struct block *) NULL, + VAR_NAMESPACE, (int *) NULL, + (struct symtab **) NULL); + if (sym) + { + write_exp_elt_opcode (OP_VAR_VALUE); + write_exp_elt_block (NULL); + write_exp_elt_sym (sym); + write_exp_elt_opcode (OP_VAR_VALUE); + break; + } + + msymbol = lookup_minimal_symbol (name, NULL, NULL); + if (msymbol != NULL) + { + write_exp_msymbol (msymbol, + lookup_function_type (builtin_type_int), + builtin_type_int); + } + else + if (!have_full_symbols () && !have_partial_symbols ()) + error ("No symbol table is loaded. Use the \"file\" command."); + else + error ("No symbol \"%s\" in current context.", name); + } + ; + +variable: name_not_typename + { struct symbol *sym = $1.sym; + + if (sym) + { + if (symbol_read_needs_frame (sym)) + { + if (innermost_block == 0 || + contained_in (block_found, + innermost_block)) + innermost_block = block_found; + } + + write_exp_elt_opcode (OP_VAR_VALUE); + /* We want to use the selected frame, not + another more inner frame which happens to + be in the same block. */ + write_exp_elt_block (NULL); + write_exp_elt_sym (sym); + write_exp_elt_opcode (OP_VAR_VALUE); + } + else if ($1.is_a_field_of_this) + { + /* Object pascal: it hangs off of `this'. Must + not inadvertently convert from a method call + to data ref. */ + if (innermost_block == 0 || + contained_in (block_found, innermost_block)) + innermost_block = block_found; + write_exp_elt_opcode (OP_THIS); + write_exp_elt_opcode (OP_THIS); + write_exp_elt_opcode (STRUCTOP_PTR); + write_exp_string ($1.stoken); + write_exp_elt_opcode (STRUCTOP_PTR); + } + else + { + struct minimal_symbol *msymbol; + register char *arg = copy_name ($1.stoken); + + msymbol = + lookup_minimal_symbol (arg, NULL, NULL); + if (msymbol != NULL) + { + write_exp_msymbol (msymbol, + lookup_function_type (builtin_type_int), + builtin_type_int); + } + else if (!have_full_symbols () && !have_partial_symbols ()) + error ("No symbol table is loaded. Use the \"file\" command."); + else + error ("No symbol \"%s\" in current context.", + copy_name ($1.stoken)); + } + } + ; + + +ptype : typebase + ; + +/* We used to try to recognize more pointer to member types here, but + that didn't work (shift/reduce conflicts meant that these rules never + got executed). The problem is that + int (foo::bar::baz::bizzle) + is a function type but + int (foo::bar::baz::bizzle::*) + is a pointer to member type. Stroustrup loses again! */ + +type : ptype + | typebase COLONCOLON '*' + { $$ = lookup_member_type (builtin_type_int, $1); } + ; + +typebase /* Implements (approximately): (type-qualifier)* type-specifier */ + : TYPENAME + { $$ = $1.type; } + | STRUCT name + { $$ = lookup_struct (copy_name ($2), + expression_context_block); } + | CLASS name + { $$ = lookup_struct (copy_name ($2), + expression_context_block); } + /* "const" and "volatile" are curently ignored. A type qualifier + after the type is handled in the ptype rule. I think these could + be too. */ + ; + +name : NAME { $$ = $1.stoken; } + | BLOCKNAME { $$ = $1.stoken; } + | TYPENAME { $$ = $1.stoken; } + | NAME_OR_INT { $$ = $1.stoken; } + ; + +name_not_typename : NAME + | BLOCKNAME +/* These would be useful if name_not_typename was useful, but it is just + a fake for "variable", so these cause reduce/reduce conflicts because + the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable, + =exp) or just an exp. If name_not_typename was ever used in an lvalue + context where only a name could occur, this might be useful. + | NAME_OR_INT + */ + ; + +%% + +/* Take care of parsing a number (anything that starts with a digit). + Set yylval and return the token type; update lexptr. + LEN is the number of characters in it. */ + +/*** Needs some error checking for the float case ***/ + +static int +parse_number (p, len, parsed_float, putithere) + register char *p; + register int len; + int parsed_float; + YYSTYPE *putithere; +{ + /* FIXME: Shouldn't these be unsigned? We don't deal with negative values + here, and we do kind of silly things like cast to unsigned. */ + register LONGEST n = 0; + register LONGEST prevn = 0; + ULONGEST un; + + register int i = 0; + register int c; + register int base = input_radix; + int unsigned_p = 0; + + /* Number of "L" suffixes encountered. */ + int long_p = 0; + + /* We have found a "L" or "U" suffix. */ + int found_suffix = 0; + + ULONGEST high_bit; + struct type *signed_type; + struct type *unsigned_type; + + if (parsed_float) + { + /* It's a float since it contains a point or an exponent. */ + char c; + int num = 0; /* number of tokens scanned by scanf */ + char saved_char = p[len]; + + p[len] = 0; /* null-terminate the token */ + if (sizeof (putithere->typed_val_float.dval) <= sizeof (float)) + num = sscanf (p, "%g%c", (float *) &putithere->typed_val_float.dval,&c); + else if (sizeof (putithere->typed_val_float.dval) <= sizeof (double)) + num = sscanf (p, "%lg%c", (double *) &putithere->typed_val_float.dval,&c); + else + { +#ifdef SCANF_HAS_LONG_DOUBLE + num = sscanf (p, "%Lg%c", &putithere->typed_val_float.dval,&c); +#else + /* Scan it into a double, then assign it to the long double. + This at least wins with values representable in the range + of doubles. */ + double temp; + num = sscanf (p, "%lg%c", &temp,&c); + putithere->typed_val_float.dval = temp; +#endif + } + p[len] = saved_char; /* restore the input stream */ + if (num != 1) /* check scanf found ONLY a float ... */ + return ERROR; + /* See if it has `f' or `l' suffix (float or long double). */ + + c = tolower (p[len - 1]); + + if (c == 'f') + putithere->typed_val_float.type = builtin_type_float; + else if (c == 'l') + putithere->typed_val_float.type = builtin_type_long_double; + else if (isdigit (c) || c == '.') + putithere->typed_val_float.type = builtin_type_double; + else + return ERROR; + + return FLOAT; + } + + /* Handle base-switching prefixes 0x, 0t, 0d, 0 */ + if (p[0] == '0') + switch (p[1]) + { + case 'x': + case 'X': + if (len >= 3) + { + p += 2; + base = 16; + len -= 2; + } + break; + + case 't': + case 'T': + case 'd': + case 'D': + if (len >= 3) + { + p += 2; + base = 10; + len -= 2; + } + break; + + default: + base = 8; + break; + } + + while (len-- > 0) + { + c = *p++; + if (c >= 'A' && c <= 'Z') + c += 'a' - 'A'; + if (c != 'l' && c != 'u') + n *= base; + if (c >= '0' && c <= '9') + { + if (found_suffix) + return ERROR; + n += i = c - '0'; + } + else + { + if (base > 10 && c >= 'a' && c <= 'f') + { + if (found_suffix) + return ERROR; + n += i = c - 'a' + 10; + } + else if (c == 'l') + { + ++long_p; + found_suffix = 1; + } + else if (c == 'u') + { + unsigned_p = 1; + found_suffix = 1; + } + else + return ERROR; /* Char not a digit */ + } + if (i >= base) + return ERROR; /* Invalid digit in this base */ + + /* Portably test for overflow (only works for nonzero values, so make + a second check for zero). FIXME: Can't we just make n and prevn + unsigned and avoid this? */ + if (c != 'l' && c != 'u' && (prevn >= n) && n != 0) + unsigned_p = 1; /* Try something unsigned */ + + /* Portably test for unsigned overflow. + FIXME: This check is wrong; for example it doesn't find overflow + on 0x123456789 when LONGEST is 32 bits. */ + if (c != 'l' && c != 'u' && n != 0) + { + if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n)) + error ("Numeric constant too large."); + } + prevn = n; + } + + /* An integer constant is an int, a long, or a long long. An L + suffix forces it to be long; an LL suffix forces it to be long + long. If not forced to a larger size, it gets the first type of + the above that it fits in. To figure out whether it fits, we + shift it right and see whether anything remains. Note that we + can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one + operation, because many compilers will warn about such a shift + (which always produces a zero result). Sometimes TARGET_INT_BIT + or TARGET_LONG_BIT will be that big, sometimes not. To deal with + the case where it is we just always shift the value more than + once, with fewer bits each time. */ + + un = (ULONGEST)n >> 2; + if (long_p == 0 + && (un >> (TARGET_INT_BIT - 2)) == 0) + { + high_bit = ((ULONGEST)1) << (TARGET_INT_BIT-1); + + /* A large decimal (not hex or octal) constant (between INT_MAX + and UINT_MAX) is a long or unsigned long, according to ANSI, + never an unsigned int, but this code treats it as unsigned + int. This probably should be fixed. GCC gives a warning on + such constants. */ + + unsigned_type = builtin_type_unsigned_int; + signed_type = builtin_type_int; + } + else if (long_p <= 1 + && (un >> (TARGET_LONG_BIT - 2)) == 0) + { + high_bit = ((ULONGEST)1) << (TARGET_LONG_BIT-1); + unsigned_type = builtin_type_unsigned_long; + signed_type = builtin_type_long; + } + else + { + high_bit = (((ULONGEST)1) + << (TARGET_LONG_LONG_BIT - 32 - 1) + << 16 + << 16); + if (high_bit == 0) + /* A long long does not fit in a LONGEST. */ + high_bit = + (ULONGEST)1 << (sizeof (LONGEST) * HOST_CHAR_BIT - 1); + unsigned_type = builtin_type_unsigned_long_long; + signed_type = builtin_type_long_long; + } + + putithere->typed_val_int.val = n; + + /* If the high bit of the worked out type is set then this number + has to be unsigned. */ + + if (unsigned_p || (n & high_bit)) + { + putithere->typed_val_int.type = unsigned_type; + } + else + { + putithere->typed_val_int.type = signed_type; + } + + return INT; +} + +struct token +{ + char *operator; + int token; + enum exp_opcode opcode; +}; + +static const struct token tokentab3[] = + { + {"shr", RSH, BINOP_END}, + {"shl", LSH, BINOP_END}, + {"and", ANDAND, BINOP_END}, + {"div", DIV, BINOP_END}, + {"not", NOT, BINOP_END}, + {"mod", MOD, BINOP_END}, + {"inc", INCREMENT, BINOP_END}, + {"dec", DECREMENT, BINOP_END}, + {"xor", XOR, BINOP_END} + }; + +static const struct token tokentab2[] = + { + {"or", OR, BINOP_END}, + {"<>", NOTEQUAL, BINOP_END}, + {"<=", LEQ, BINOP_END}, + {">=", GEQ, BINOP_END}, + {":=", ASSIGN, BINOP_END} + }; + +/* Allocate uppercased var */ +/* make an uppercased copy of tokstart */ +static char * uptok (tokstart, namelen) + char *tokstart; + int namelen; +{ + int i; + char *uptokstart = (char *)malloc(namelen+1); + for (i = 0;i <= namelen;i++) + { + if ((tokstart[i]>='a' && tokstart[i]<='z')) + uptokstart[i] = tokstart[i]-('a'-'A'); + else + uptokstart[i] = tokstart[i]; + } + uptokstart[namelen]='\0'; + return uptokstart; +} +/* Read one token, getting characters through lexptr. */ + + +static int +yylex () +{ + int c; + int namelen; + unsigned int i; + char *tokstart; + char *uptokstart; + char *tokptr; + char *p; + int tempbufindex; + static char *tempbuf; + static int tempbufsize; + + retry: + + tokstart = lexptr; + /* See if it is a special token of length 3. */ + for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++) + if (STREQN (tokstart, tokentab3[i].operator, 3)) + { + lexptr += 3; + yylval.opcode = tokentab3[i].opcode; + return tokentab3[i].token; + } + + /* See if it is a special token of length 2. */ + for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++) + if (STREQN (tokstart, tokentab2[i].operator, 2)) + { + lexptr += 2; + yylval.opcode = tokentab2[i].opcode; + return tokentab2[i].token; + } + + switch (c = *tokstart) + { + case 0: + return 0; + + case ' ': + case '\t': + case '\n': + lexptr++; + goto retry; + + case '\'': + /* We either have a character constant ('0' or '\177' for example) + or we have a quoted symbol reference ('foo(int,int)' in object pascal + for example). */ + lexptr++; + c = *lexptr++; + if (c == '\\') + c = parse_escape (&lexptr); + else if (c == '\'') + error ("Empty character constant."); + + yylval.typed_val_int.val = c; + yylval.typed_val_int.type = builtin_type_char; + + c = *lexptr++; + if (c != '\'') + { + namelen = skip_quoted (tokstart) - tokstart; + if (namelen > 2) + { + lexptr = tokstart + namelen; + if (lexptr[-1] != '\'') + error ("Unmatched single quote."); + namelen -= 2; + tokstart++; + uptokstart = uptok(tokstart,namelen); + goto tryname; + } + error ("Invalid character constant."); + } + return INT; + + case '(': + paren_depth++; + lexptr++; + return c; + + case ')': + if (paren_depth == 0) + return 0; + paren_depth--; + lexptr++; + return c; + + case ',': + if (comma_terminates && paren_depth == 0) + return 0; + lexptr++; + return c; + + case '.': + /* Might be a floating point number. */ + if (lexptr[1] < '0' || lexptr[1] > '9') + goto symbol; /* Nope, must be a symbol. */ + /* FALL THRU into number case. */ + + case '0': + case '1': + case '2': + case '3': + case '4': + case '5': + case '6': + case '7': + case '8': + case '9': + { + /* It's a number. */ + int got_dot = 0, got_e = 0, toktype; + register char *p = tokstart; + int hex = input_radix > 10; + + if (c == '0' && (p[1] == 'x' || p[1] == 'X')) + { + p += 2; + hex = 1; + } + else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D')) + { + p += 2; + hex = 0; + } + + for (;; ++p) + { + /* This test includes !hex because 'e' is a valid hex digit + and thus does not indicate a floating point number when + the radix is hex. */ + if (!hex && !got_e && (*p == 'e' || *p == 'E')) + got_dot = got_e = 1; + /* This test does not include !hex, because a '.' always indicates + a decimal floating point number regardless of the radix. */ + else if (!got_dot && *p == '.') + got_dot = 1; + else if (got_e && (p[-1] == 'e' || p[-1] == 'E') + && (*p == '-' || *p == '+')) + /* This is the sign of the exponent, not the end of the + number. */ + continue; + /* We will take any letters or digits. parse_number will + complain if past the radix, or if L or U are not final. */ + else if ((*p < '0' || *p > '9') + && ((*p < 'a' || *p > 'z') + && (*p < 'A' || *p > 'Z'))) + break; + } + toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval); + if (toktype == ERROR) + { + char *err_copy = (char *) alloca (p - tokstart + 1); + + memcpy (err_copy, tokstart, p - tokstart); + err_copy[p - tokstart] = 0; + error ("Invalid number \"%s\".", err_copy); + } + lexptr = p; + return toktype; + } + + case '+': + case '-': + case '*': + case '/': + case '|': + case '&': + case '^': + case '~': + case '!': + case '@': + case '<': + case '>': + case '[': + case ']': + case '?': + case ':': + case '=': + case '{': + case '}': + symbol: + lexptr++; + return c; + + case '"': + + /* Build the gdb internal form of the input string in tempbuf, + translating any standard C escape forms seen. Note that the + buffer is null byte terminated *only* for the convenience of + debugging gdb itself and printing the buffer contents when + the buffer contains no embedded nulls. Gdb does not depend + upon the buffer being null byte terminated, it uses the length + string instead. This allows gdb to handle C strings (as well + as strings in other languages) with embedded null bytes */ + + tokptr = ++tokstart; + tempbufindex = 0; + + do { + /* Grow the static temp buffer if necessary, including allocating + the first one on demand. */ + if (tempbufindex + 1 >= tempbufsize) + { + tempbuf = (char *) realloc (tempbuf, tempbufsize += 64); + } + switch (*tokptr) + { + case '\0': + case '"': + /* Do nothing, loop will terminate. */ + break; + case '\\': + tokptr++; + c = parse_escape (&tokptr); + if (c == -1) + { + continue; + } + tempbuf[tempbufindex++] = c; + break; + default: + tempbuf[tempbufindex++] = *tokptr++; + break; + } + } while ((*tokptr != '"') && (*tokptr != '\0')); + if (*tokptr++ != '"') + { + error ("Unterminated string in expression."); + } + tempbuf[tempbufindex] = '\0'; /* See note above */ + yylval.sval.ptr = tempbuf; + yylval.sval.length = tempbufindex; + lexptr = tokptr; + return (STRING); + } + + if (!(c == '_' || c == '$' + || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'))) + /* We must have come across a bad character (e.g. ';'). */ + error ("Invalid character '%c' in expression.", c); + + /* It's a name. See how long it is. */ + namelen = 0; + for (c = tokstart[namelen]; + (c == '_' || c == '$' || (c >= '0' && c <= '9') + || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');) + { + /* Template parameter lists are part of the name. + FIXME: This mishandles `print $a<4&&$a>3'. */ + if (c == '<') + { + int i = namelen; + int nesting_level = 1; + while (tokstart[++i]) + { + if (tokstart[i] == '<') + nesting_level++; + else if (tokstart[i] == '>') + { + if (--nesting_level == 0) + break; + } + } + if (tokstart[i] == '>') + namelen = i; + else + break; + } + + /* do NOT uppercase internals because of registers !!! */ + c = tokstart[++namelen]; + } + + uptokstart = uptok(tokstart,namelen); + + /* The token "if" terminates the expression and is NOT + removed from the input stream. */ + if (namelen == 2 && uptokstart[0] == 'I' && uptokstart[1] == 'F') + { + return 0; + } + + lexptr += namelen; + + tryname: + + /* Catch specific keywords. Should be done with a data structure. */ + switch (namelen) + { + case 6: + if (STREQ (uptokstart, "OBJECT")) + return CLASS; + if (STREQ (uptokstart, "RECORD")) + return STRUCT; + if (STREQ (uptokstart, "SIZEOF")) + return SIZEOF; + break; + case 5: + if (STREQ (uptokstart, "CLASS")) + return CLASS; + if (STREQ (uptokstart, "FALSE")) + { + yylval.lval = 0; + return FALSE; + } + break; + case 4: + if (STREQ (uptokstart, "TRUE")) + { + yylval.lval = 1; + return TRUE; + } + if (STREQ (uptokstart, "SELF")) + { + /* here we search for 'this' like + inserted in FPC stabs debug info */ + static const char this_name[] = + { /* CPLUS_MARKER,*/ 't', 'h', 'i', 's', '\0' }; + + if (lookup_symbol (this_name, expression_context_block, + VAR_NAMESPACE, (int *) NULL, + (struct symtab **) NULL)) + return THIS; + } + break; + default: + break; + } + + yylval.sval.ptr = tokstart; + yylval.sval.length = namelen; + + if (*tokstart == '$') + { + /* $ is the normal prefix for pascal hexadecimal values + but this conflicts with the GDB use for debugger variables + so in expression to enter hexadecimal values + we still need to use C syntax with 0xff */ + write_dollar_variable (yylval.sval); + return VARIABLE; + } + + /* Use token-type BLOCKNAME for symbols that happen to be defined as + functions or symtabs. If this is not so, then ... + Use token-type TYPENAME for symbols that happen to be defined + currently as names of types; NAME for other symbols. + The caller is not constrained to care about the distinction. */ + { + char *tmp = copy_name (yylval.sval); + struct symbol *sym; + int is_a_field_of_this = 0; + int hextype; + + sym = lookup_symbol (tmp, expression_context_block, + VAR_NAMESPACE, + &is_a_field_of_this, + (struct symtab **) NULL); + /* second chance uppercased ! */ + if (!sym) + { + for (i = 0;i <= namelen;i++) + { + if ((tmp[i]>='a' && tmp[i]<='z')) + tmp[i] -= ('a'-'A'); + /* I am not sure that copy_name gives excatly the same result ! */ + if ((tokstart[i]>='a' && tokstart[i]<='z')) + tokstart[i] -= ('a'-'A'); + } + sym = lookup_symbol (tmp, expression_context_block, + VAR_NAMESPACE, + &is_a_field_of_this, + (struct symtab **) NULL); + } + /* Call lookup_symtab, not lookup_partial_symtab, in case there are + no psymtabs (coff, xcoff, or some future change to blow away the + psymtabs once once symbols are read). */ + if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) || + lookup_symtab (tmp)) + { + yylval.ssym.sym = sym; + yylval.ssym.is_a_field_of_this = is_a_field_of_this; + return BLOCKNAME; + } + if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF) + { +#if 1 + /* Despite the following flaw, we need to keep this code enabled. + Because we can get called from check_stub_method, if we don't + handle nested types then it screws many operations in any + program which uses nested types. */ + /* In "A::x", if x is a member function of A and there happens + to be a type (nested or not, since the stabs don't make that + distinction) named x, then this code incorrectly thinks we + are dealing with nested types rather than a member function. */ + + char *p; + char *namestart; + struct symbol *best_sym; + + /* Look ahead to detect nested types. This probably should be + done in the grammar, but trying seemed to introduce a lot + of shift/reduce and reduce/reduce conflicts. It's possible + that it could be done, though. Or perhaps a non-grammar, but + less ad hoc, approach would work well. */ + + /* Since we do not currently have any way of distinguishing + a nested type from a non-nested one (the stabs don't tell + us whether a type is nested), we just ignore the + containing type. */ + + p = lexptr; + best_sym = sym; + while (1) + { + /* Skip whitespace. */ + while (*p == ' ' || *p == '\t' || *p == '\n') + ++p; + if (*p == ':' && p[1] == ':') + { + /* Skip the `::'. */ + p += 2; + /* Skip whitespace. */ + while (*p == ' ' || *p == '\t' || *p == '\n') + ++p; + namestart = p; + while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9') + || (*p >= 'a' && *p <= 'z') + || (*p >= 'A' && *p <= 'Z')) + ++p; + if (p != namestart) + { + struct symbol *cur_sym; + /* As big as the whole rest of the expression, which is + at least big enough. */ + char *ncopy = alloca (strlen (tmp)+strlen (namestart)+3); + char *tmp1; + + tmp1 = ncopy; + memcpy (tmp1, tmp, strlen (tmp)); + tmp1 += strlen (tmp); + memcpy (tmp1, "::", 2); + tmp1 += 2; + memcpy (tmp1, namestart, p - namestart); + tmp1[p - namestart] = '\0'; + cur_sym = lookup_symbol (ncopy, expression_context_block, + VAR_NAMESPACE, (int *) NULL, + (struct symtab **) NULL); + if (cur_sym) + { + if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF) + { + best_sym = cur_sym; + lexptr = p; + } + else + break; + } + else + break; + } + else + break; + } + else + break; + } + + yylval.tsym.type = SYMBOL_TYPE (best_sym); +#else /* not 0 */ + yylval.tsym.type = SYMBOL_TYPE (sym); +#endif /* not 0 */ + return TYPENAME; + } + if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0) + return TYPENAME; + + /* Input names that aren't symbols but ARE valid hex numbers, + when the input radix permits them, can be names or numbers + depending on the parse. Note we support radixes > 16 here. */ + if (!sym && + ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) || + (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10))) + { + YYSTYPE newlval; /* Its value is ignored. */ + hextype = parse_number (tokstart, namelen, 0, &newlval); + if (hextype == INT) + { + yylval.ssym.sym = sym; + yylval.ssym.is_a_field_of_this = is_a_field_of_this; + return NAME_OR_INT; + } + } + + free(uptokstart); + /* Any other kind of symbol */ + yylval.ssym.sym = sym; + yylval.ssym.is_a_field_of_this = is_a_field_of_this; + return NAME; + } +} + +void +yyerror (msg) + char *msg; +{ + error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr); +} + diff --git a/gdb/p-lang.c b/gdb/p-lang.c new file mode 100644 index 0000000..db33eb7 --- /dev/null +++ b/gdb/p-lang.c @@ -0,0 +1,430 @@ +/* Pascal language support routines for GDB, the GNU debugger. + Copyright 2000 Free Software Foundation, Inc. + + This file is part of GDB. + + This program is free software; you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation; either version 2 of the License, or + (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program; if not, write to the Free Software + Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */ + +/* This file is derived from p-lang.c */ + +#include "defs.h" +#include "symtab.h" +#include "gdbtypes.h" +#include "expression.h" +#include "parser-defs.h" +#include "language.h" +#include "p-lang.h" +#include "valprint.h" + +extern void _initialize_pascal_language (void); +static void pascal_one_char (int, struct ui_file *, int *); + +/* Print the character C on STREAM as part of the contents of a literal + string. + In_quotes is reset to 0 if a char is written with #4 notation */ + +static void +pascal_one_char (c, stream, in_quotes) + register int c; + struct ui_file *stream; + int *in_quotes; +{ + + c &= 0xFF; /* Avoid sign bit follies */ + + if ((c == '\'') || (PRINT_LITERAL_FORM (c))) + { + if (!(*in_quotes)) + fputs_filtered ("'", stream); + *in_quotes = 1; + if (c == '\'') + { + fputs_filtered ("''", stream); + } + else + fprintf_filtered (stream, "%c", c); + } + else + { + if (*in_quotes) + fputs_filtered ("'", stream); + *in_quotes = 0; + fprintf_filtered (stream, "#%d", (unsigned int) c); + } +} + +static void pascal_emit_char (int c, struct ui_file *stream, int quoter); + +/* Print the character C on STREAM as part of the contents of a literal + string whose delimiter is QUOTER. Note that that format for printing + characters and strings is language specific. */ + +static void +pascal_emit_char (c, stream, quoter) + register int c; + struct ui_file *stream; + int quoter; +{ + int in_quotes = 0; + pascal_one_char (c, stream, &in_quotes); + if (in_quotes) + fputs_filtered ("'", stream); +} + +void +pascal_printchar (c, stream) + int c; + struct ui_file *stream; +{ + int in_quotes = 0; + pascal_one_char (c, stream, &in_quotes); + if (in_quotes) + fputs_filtered ("'", stream); +} + +/* Print the character string STRING, printing at most LENGTH characters. + Printing stops early if the number hits print_max; repeat counts + are printed as appropriate. Print ellipses at the end if we + had to stop before printing LENGTH characters, or if FORCE_ELLIPSES. */ + +void +pascal_printstr (stream, string, length, width, force_ellipses) + struct ui_file *stream; + char *string; + unsigned int length; + int width; + int force_ellipses; +{ + register unsigned int i; + unsigned int things_printed = 0; + int in_quotes = 0; + int need_comma = 0; + extern int inspect_it; + + /* If the string was not truncated due to `set print elements', and + the last byte of it is a null, we don't print that, in traditional C + style. */ + if ((!force_ellipses) && length > 0 && string[length - 1] == '\0') + length--; + + if (length == 0) + { + fputs_filtered ("''", stream); + return; + } + + for (i = 0; i < length && things_printed < print_max; ++i) + { + /* Position of the character we are examining + to see whether it is repeated. */ + unsigned int rep1; + /* Number of repetitions we have detected so far. */ + unsigned int reps; + + QUIT; + + if (need_comma) + { + fputs_filtered (", ", stream); + need_comma = 0; + } + + rep1 = i + 1; + reps = 1; + while (rep1 < length && string[rep1] == string[i]) + { + ++rep1; + ++reps; + } + + if (reps > repeat_count_threshold) + { + if (in_quotes) + { + if (inspect_it) + fputs_filtered ("\\', ", stream); + else + fputs_filtered ("', ", stream); + in_quotes = 0; + } + pascal_printchar (string[i], stream); + fprintf_filtered (stream, " <repeats %u times>", reps); + i = rep1 - 1; + things_printed += repeat_count_threshold; + need_comma = 1; + } + else + { + int c = string[i]; + if ((!in_quotes) && (PRINT_LITERAL_FORM (c))) + { + if (inspect_it) + fputs_filtered ("\\'", stream); + else + fputs_filtered ("'", stream); + in_quotes = 1; + } + pascal_one_char (c, stream, &in_quotes); + ++things_printed; + } + } + + /* Terminate the quotes if necessary. */ + if (in_quotes) + { + if (inspect_it) + fputs_filtered ("\\'", stream); + else + fputs_filtered ("'", stream); + } + + if (force_ellipses || i < length) + fputs_filtered ("...", stream); +} + +/* Create a fundamental Pascal type using default reasonable for the current + target machine. + + Some object/debugging file formats (DWARF version 1, COFF, etc) do not + define fundamental types such as "int" or "double". Others (stabs or + DWARF version 2, etc) do define fundamental types. For the formats which + don't provide fundamental types, gdb can create such types using this + function. + + FIXME: Some compilers distinguish explicitly signed integral types + (signed short, signed int, signed long) from "regular" integral types + (short, int, long) in the debugging information. There is some dis- + agreement as to how useful this feature is. In particular, gcc does + not support this. Also, only some debugging formats allow the + distinction to be passed on to a debugger. For now, we always just + use "short", "int", or "long" as the type name, for both the implicit + and explicitly signed types. This also makes life easier for the + gdb test suite since we don't have to account for the differences + in output depending upon what the compiler and debugging format + support. We will probably have to re-examine the issue when gdb + starts taking it's fundamental type information directly from the + debugging information supplied by the compiler. fnf@cygnus.com */ + +/* Note there might be some discussion about the choosen correspondance + because it mainly reflects Free Pascal Compiler setup for now PM */ + + +struct type * +pascal_create_fundamental_type (objfile, typeid) + struct objfile *objfile; + int typeid; +{ + register struct type *type = NULL; + + switch (typeid) + { + default: + /* FIXME: For now, if we are asked to produce a type not in this + language, create the equivalent of a C integer type with the + name "<?type?>". When all the dust settles from the type + reconstruction work, this should probably become an error. */ + type = init_type (TYPE_CODE_INT, + TARGET_INT_BIT / TARGET_CHAR_BIT, + 0, "<?type?>", objfile); + warning ("internal error: no Pascal fundamental type %d", typeid); + break; + case FT_VOID: + type = init_type (TYPE_CODE_VOID, + TARGET_CHAR_BIT / TARGET_CHAR_BIT, + 0, "void", objfile); + break; + case FT_CHAR: + type = init_type (TYPE_CODE_INT, + TARGET_CHAR_BIT / TARGET_CHAR_BIT, + 0, "char", objfile); + break; + case FT_SIGNED_CHAR: + type = init_type (TYPE_CODE_INT, + TARGET_CHAR_BIT / TARGET_CHAR_BIT, + 0, "shortint", objfile); + break; + case FT_UNSIGNED_CHAR: + type = init_type (TYPE_CODE_INT, + TARGET_CHAR_BIT / TARGET_CHAR_BIT, + TYPE_FLAG_UNSIGNED, "byte", objfile); + break; + case FT_SHORT: + type = init_type (TYPE_CODE_INT, + TARGET_SHORT_BIT / TARGET_CHAR_BIT, + 0, "integer", objfile); + break; + case FT_SIGNED_SHORT: + type = init_type (TYPE_CODE_INT, + TARGET_SHORT_BIT / TARGET_CHAR_BIT, + 0, "integer", objfile); /* FIXME-fnf */ + break; + case FT_UNSIGNED_SHORT: + type = init_type (TYPE_CODE_INT, + TARGET_SHORT_BIT / TARGET_CHAR_BIT, + TYPE_FLAG_UNSIGNED, "word", objfile); + break; + case FT_INTEGER: + type = init_type (TYPE_CODE_INT, + TARGET_INT_BIT / TARGET_CHAR_BIT, + 0, "longint", objfile); + break; + case FT_SIGNED_INTEGER: + type = init_type (TYPE_CODE_INT, + TARGET_INT_BIT / TARGET_CHAR_BIT, + 0, "longint", objfile); /* FIXME -fnf */ + break; + case FT_UNSIGNED_INTEGER: + type = init_type (TYPE_CODE_INT, + TARGET_INT_BIT / TARGET_CHAR_BIT, + TYPE_FLAG_UNSIGNED, "cardinal", objfile); + break; + case FT_LONG: + type = init_type (TYPE_CODE_INT, + TARGET_LONG_BIT / TARGET_CHAR_BIT, + 0, "long", objfile); + break; + case FT_SIGNED_LONG: + type = init_type (TYPE_CODE_INT, + TARGET_LONG_BIT / TARGET_CHAR_BIT, + 0, "long", objfile); /* FIXME -fnf */ + break; + case FT_UNSIGNED_LONG: + type = init_type (TYPE_CODE_INT, + TARGET_LONG_BIT / TARGET_CHAR_BIT, + TYPE_FLAG_UNSIGNED, "unsigned long", objfile); + break; + case FT_LONG_LONG: + type = init_type (TYPE_CODE_INT, + TARGET_LONG_LONG_BIT / TARGET_CHAR_BIT, + 0, "long long", objfile); + break; + case FT_SIGNED_LONG_LONG: + type = init_type (TYPE_CODE_INT, + TARGET_LONG_LONG_BIT / TARGET_CHAR_BIT, + 0, "signed long long", objfile); + break; + case FT_UNSIGNED_LONG_LONG: + type = init_type (TYPE_CODE_INT, + TARGET_LONG_LONG_BIT / TARGET_CHAR_BIT, + TYPE_FLAG_UNSIGNED, "unsigned long long", objfile); + break; + case FT_FLOAT: + type = init_type (TYPE_CODE_FLT, + TARGET_FLOAT_BIT / TARGET_CHAR_BIT, + 0, "float", objfile); + break; + case FT_DBL_PREC_FLOAT: + type = init_type (TYPE_CODE_FLT, + TARGET_DOUBLE_BIT / TARGET_CHAR_BIT, + 0, "double", objfile); + break; + case FT_EXT_PREC_FLOAT: + type = init_type (TYPE_CODE_FLT, + TARGET_LONG_DOUBLE_BIT / TARGET_CHAR_BIT, + 0, "extended", objfile); + break; + } + return (type); +} + + +/* Table mapping opcodes into strings for printing operators + and precedences of the operators. */ + +const struct op_print pascal_op_print_tab[] = +{ + {",", BINOP_COMMA, PREC_COMMA, 0}, + {":=", BINOP_ASSIGN, PREC_ASSIGN, 1}, + {"or", BINOP_BITWISE_IOR, PREC_BITWISE_IOR, 0}, + {"xor", BINOP_BITWISE_XOR, PREC_BITWISE_XOR, 0}, + {"and", BINOP_BITWISE_AND, PREC_BITWISE_AND, 0}, + {"=", BINOP_EQUAL, PREC_EQUAL, 0}, + {"<>", BINOP_NOTEQUAL, PREC_EQUAL, 0}, + {"<=", BINOP_LEQ, PREC_ORDER, 0}, + {">=", BINOP_GEQ, PREC_ORDER, 0}, + {">", BINOP_GTR, PREC_ORDER, 0}, + {"<", BINOP_LESS, PREC_ORDER, 0}, + {"shr", BINOP_RSH, PREC_SHIFT, 0}, + {"shl", BINOP_LSH, PREC_SHIFT, 0}, + {"+", BINOP_ADD, PREC_ADD, 0}, + {"-", BINOP_SUB, PREC_ADD, 0}, + {"*", BINOP_MUL, PREC_MUL, 0}, + {"/", BINOP_DIV, PREC_MUL, 0}, + {"div", BINOP_INTDIV, PREC_MUL, 0}, + {"mod", BINOP_REM, PREC_MUL, 0}, + {"@", BINOP_REPEAT, PREC_REPEAT, 0}, + {"-", UNOP_NEG, PREC_PREFIX, 0}, + {"not", UNOP_LOGICAL_NOT, PREC_PREFIX, 0}, + {"^", UNOP_IND, PREC_SUFFIX, 1}, + {"@", UNOP_ADDR, PREC_PREFIX, 0}, + {"sizeof", UNOP_SIZEOF, PREC_PREFIX, 0}, + {NULL, 0, 0, 0} +}; + +struct type **const /* CONST_PTR v 4.17 */ (pascal_builtin_types[]) = +{ + &builtin_type_int, + &builtin_type_long, + &builtin_type_short, + &builtin_type_char, + &builtin_type_float, + &builtin_type_double, + &builtin_type_void, + &builtin_type_long_long, + &builtin_type_signed_char, + &builtin_type_unsigned_char, + &builtin_type_unsigned_short, + &builtin_type_unsigned_int, + &builtin_type_unsigned_long, + &builtin_type_unsigned_long_long, + &builtin_type_long_double, + &builtin_type_complex, + &builtin_type_double_complex, + 0 +}; + +const struct language_defn pascal_language_defn = +{ + "pascal", /* Language name */ + language_pascal, + pascal_builtin_types, + range_check_on, + type_check_on, + pascal_parse, + pascal_error, + evaluate_subexp_standard, + pascal_printchar, /* Print a character constant */ + pascal_printstr, /* Function to print string constant */ + pascal_emit_char, /* Print a single char */ + pascal_create_fundamental_type, /* Create fundamental type in this language */ + pascal_print_type, /* Print a type using appropriate syntax */ + pascal_val_print, /* Print a value using appropriate syntax */ + pascal_value_print, /* Print a top-level value */ + {"", "%", "b", ""}, /* Binary format info */ + {"0%lo", "0", "o", ""}, /* Octal format info */ + {"%ld", "", "d", ""}, /* Decimal format info */ + {"$%lx", "$", "x", ""}, /* Hex format info */ + pascal_op_print_tab, /* expression operators for printing */ + 1, /* c-style arrays */ + 0, /* String lower bound */ + &builtin_type_char, /* Type of string elements */ + LANG_MAGIC +}; + +void +_initialize_pascal_language () +{ + add_language (&pascal_language_defn); +} diff --git a/gdb/p-lang.h b/gdb/p-lang.h new file mode 100644 index 0000000..c03e632 --- /dev/null +++ b/gdb/p-lang.h @@ -0,0 +1,75 @@ +/* Pascal language support definitions for GDB, the GNU debugger. + Copyright 2000 Free Software Foundation, Inc. + + This file is part of GDB. + + This program is free software; you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation; either version 2 of the License, or + (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program; if not, write to the Free Software + Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */ + +/* This file is derived from c-lang.h */ + +#ifdef __STDC__ /* Forward decls for prototypes */ +struct value; +#endif + +extern int pascal_parse (void); /* Defined in p-exp.y */ + +extern void pascal_error (char *); /* Defined in p-exp.y */ + +/* Defined in p-typeprint.c */ +extern void pascal_print_type (struct type *, char *, struct ui_file *, int, int); + +extern int pascal_val_print (struct type *, char *, int, CORE_ADDR, struct ui_file *, int, int, + int, enum val_prettyprint); + +extern int pascal_value_print (struct value *, struct ui_file *, int, enum val_prettyprint); + +extern void pascal_type_print_method_args (char *, char *, + struct ui_file *); + +/* These are in p-lang.c: */ + +extern void pascal_printchar (int, struct ui_file *); + +extern void pascal_printstr (struct ui_file *, char *, unsigned int, int, int); + +extern struct type *pascal_create_fundamental_type (struct objfile *, int); + +extern struct type **const (pascal_builtin_types[]); + +/* These are in p-typeprint.c: */ + +extern void + pascal_type_print_base (struct type *, struct ui_file *, int, int); + +extern void + pascal_type_print_varspec_prefix (struct type *, struct ui_file *, int, int); + +/* These are in cp-valprint.c */ + +extern int vtblprint; /* Controls printing of vtbl's */ + +extern int static_field_print; + +extern void pascal_object_print_class_member (char *, struct type *, struct ui_file *, char *); + +extern void pascal_object_print_class_method (char *, struct type *, struct ui_file *); + +extern void pascal_object_print_value_fields (struct type *, char *, CORE_ADDR, + struct ui_file *, int, int, enum val_prettyprint, + struct type **, int); + +extern int pascal_object_is_vtbl_ptr_type (struct type *); + +extern int pascal_object_is_vtbl_member (struct type *); diff --git a/gdb/p-typeprint.c b/gdb/p-typeprint.c new file mode 100644 index 0000000..a2cfadb --- /dev/null +++ b/gdb/p-typeprint.c @@ -0,0 +1,882 @@ +/* Support for printing Pascal types for GDB, the GNU debugger. + Copyright 2000 + Free Software Foundation, Inc. + + This file is part of GDB. + + This program is free software; you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation; either version 2 of the License, or + (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program; if not, write to the Free Software + Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */ + +/* This file is derived from p-typeprint.c */ + +#include "defs.h" +#include "obstack.h" +#include "bfd.h" /* Binary File Description */ +#include "symtab.h" +#include "gdbtypes.h" +#include "expression.h" +#include "value.h" +#include "gdbcore.h" +#include "target.h" +#include "command.h" +#include "gdbcmd.h" +#include "language.h" +#include "demangle.h" +#include "p-lang.h" +#include "typeprint.h" + +#include "gdb_string.h" +#include <errno.h> +#include <ctype.h> + +static void pascal_type_print_args (struct type *, struct ui_file *); + +static void pascal_type_print_varspec_suffix (struct type *, struct ui_file *, int, int, int); + +static void pascal_type_print_derivation_info (struct ui_file *, struct type *); + +void pascal_type_print_varspec_prefix (struct type *, struct ui_file *, int, int); + + +/* LEVEL is the depth to indent lines by. */ + +void +pascal_print_type (type, varstring, stream, show, level) + struct type *type; + char *varstring; + struct ui_file *stream; + int show; + int level; +{ + register enum type_code code; + int demangled_args; + + code = TYPE_CODE (type); + + if (show > 0) + CHECK_TYPEDEF (type); + + if ((code == TYPE_CODE_FUNC || + code == TYPE_CODE_METHOD)) + { + pascal_type_print_varspec_prefix (type, stream, show, 0); + } + /* first the name */ + fputs_filtered (varstring, stream); + + if ((varstring != NULL && *varstring != '\0') && + !(code == TYPE_CODE_FUNC || + code == TYPE_CODE_METHOD)) + { + fputs_filtered (" : ", stream); + } + + if (!(code == TYPE_CODE_FUNC || + code == TYPE_CODE_METHOD)) + { + pascal_type_print_varspec_prefix (type, stream, show, 0); + } + + pascal_type_print_base (type, stream, show, level); + /* For demangled function names, we have the arglist as part of the name, + so don't print an additional pair of ()'s */ + + demangled_args = varstring ? strchr (varstring, '(') != NULL : 0; + pascal_type_print_varspec_suffix (type, stream, show, 0, demangled_args); + +} + +/* If TYPE is a derived type, then print out derivation information. + Print only the actual base classes of this type, not the base classes + of the base classes. I.E. for the derivation hierarchy: + + class A { int a; }; + class B : public A {int b; }; + class C : public B {int c; }; + + Print the type of class C as: + + class C : public B { + int c; + } + + Not as the following (like gdb used to), which is not legal C++ syntax for + derived types and may be confused with the multiple inheritance form: + + class C : public B : public A { + int c; + } + + In general, gdb should try to print the types as closely as possible to + the form that they appear in the source code. */ + +static void +pascal_type_print_derivation_info (stream, type) + struct ui_file *stream; + struct type *type; +{ + char *name; + int i; + + for (i = 0; i < TYPE_N_BASECLASSES (type); i++) + { + fputs_filtered (i == 0 ? ": " : ", ", stream); + fprintf_filtered (stream, "%s%s ", + BASETYPE_VIA_PUBLIC (type, i) ? "public" : "private", + BASETYPE_VIA_VIRTUAL (type, i) ? " virtual" : ""); + name = type_name_no_tag (TYPE_BASECLASS (type, i)); + fprintf_filtered (stream, "%s", name ? name : "(null)"); + } + if (i > 0) + { + fputs_filtered (" ", stream); + } +} + +/* Print the Pascal method arguments ARGS to the file STREAM. */ + +void +pascal_type_print_method_args (physname, methodname, stream) + char *physname; + char *methodname; + struct ui_file *stream; +{ + int is_constructor = STREQN (physname, "__ct__", 6); + int is_destructor = STREQN (physname, "__dt__", 6); + + if (is_constructor || is_destructor) + { + physname += 6; + } + + fputs_filtered (methodname, stream); + + if (physname && (*physname != 0)) + { + int i = 0; + int len = 0; + char storec; + char *argname; + fputs_filtered (" (", stream); + /* we must demangle this */ + while isdigit + (physname[0]) + { + while isdigit + (physname[len]) + { + len++; + } + i = strtol (physname, &argname, 0); + physname += len; + storec = physname[i]; + physname[i] = 0; + fputs_filtered (physname, stream); + physname[i] = storec; + physname += i; + if (physname[0] != 0) + { + fputs_filtered (", ", stream); + } + } + fputs_filtered (")", stream); + } +} + +/* Print any asterisks or open-parentheses needed before the + variable name (to describe its type). + + On outermost call, pass 0 for PASSED_A_PTR. + On outermost call, SHOW > 0 means should ignore + any typename for TYPE and show its details. + SHOW is always zero on recursive calls. */ + +void +pascal_type_print_varspec_prefix (type, stream, show, passed_a_ptr) + struct type *type; + struct ui_file *stream; + int show; + int passed_a_ptr; +{ + char *name; + if (type == 0) + return; + + if (TYPE_NAME (type) && show <= 0) + return; + + QUIT; + + switch (TYPE_CODE (type)) + { + case TYPE_CODE_PTR: + fprintf_filtered (stream, "^"); + pascal_type_print_varspec_prefix (TYPE_TARGET_TYPE (type), stream, 0, 1); + break; /* pointer should be handled normally in pascal */ + + case TYPE_CODE_MEMBER: + if (passed_a_ptr) + fprintf_filtered (stream, "("); + pascal_type_print_varspec_prefix (TYPE_TARGET_TYPE (type), stream, 0, 0); + fprintf_filtered (stream, " "); + name = type_name_no_tag (TYPE_DOMAIN_TYPE (type)); + if (name) + fputs_filtered (name, stream); + else + pascal_type_print_base (TYPE_DOMAIN_TYPE (type), stream, 0, passed_a_ptr); + fprintf_filtered (stream, "::"); + break; + + case TYPE_CODE_METHOD: + if (passed_a_ptr) + fprintf_filtered (stream, "("); + if (TYPE_CODE (TYPE_TARGET_TYPE (type)) != TYPE_CODE_VOID) + { + fprintf_filtered (stream, "function "); + } + else + { + fprintf_filtered (stream, "procedure "); + } + + if (passed_a_ptr) + { + fprintf_filtered (stream, " "); + pascal_type_print_base (TYPE_DOMAIN_TYPE (type), stream, 0, passed_a_ptr); + fprintf_filtered (stream, "::"); + } + break; + + case TYPE_CODE_REF: + pascal_type_print_varspec_prefix (TYPE_TARGET_TYPE (type), stream, 0, 1); + fprintf_filtered (stream, "&"); + break; + + case TYPE_CODE_FUNC: + if (passed_a_ptr) + fprintf_filtered (stream, "("); + + if (TYPE_CODE (TYPE_TARGET_TYPE (type)) != TYPE_CODE_VOID) + { + fprintf_filtered (stream, "function "); + } + else + { + fprintf_filtered (stream, "procedure "); + } + + break; + + case TYPE_CODE_ARRAY: + if (passed_a_ptr) + fprintf_filtered (stream, "("); + fprintf_filtered (stream, "array "); + if (TYPE_LENGTH (type) >= 0 && TYPE_LENGTH (TYPE_TARGET_TYPE (type)) > 0 + && TYPE_ARRAY_UPPER_BOUND_TYPE (type) != BOUND_CANNOT_BE_DETERMINED) + fprintf_filtered (stream, "[%d..%d] ", + TYPE_ARRAY_LOWER_BOUND_VALUE (type), + TYPE_ARRAY_UPPER_BOUND_VALUE (type) + ); + fprintf_filtered (stream, "of "); + break; + + case TYPE_CODE_UNDEF: + case TYPE_CODE_STRUCT: + case TYPE_CODE_UNION: + case TYPE_CODE_ENUM: + case TYPE_CODE_INT: + case TYPE_CODE_FLT: + case TYPE_CODE_VOID: + case TYPE_CODE_ERROR: + case TYPE_CODE_CHAR: + case TYPE_CODE_BOOL: + case TYPE_CODE_SET: + case TYPE_CODE_RANGE: + case TYPE_CODE_STRING: + case TYPE_CODE_BITSTRING: + case TYPE_CODE_COMPLEX: + case TYPE_CODE_TYPEDEF: + case TYPE_CODE_TEMPLATE: + /* These types need no prefix. They are listed here so that + gcc -Wall will reveal any types that haven't been handled. */ + break; + default: + error ("type not handled in pascal_type_print_varspec_prefix()"); + break; + } +} + +static void +pascal_type_print_args (type, stream) + struct type *type; + struct ui_file *stream; +{ + int i; + struct type **args; + + /* fprintf_filtered (stream, "("); + no () for procedures !! */ + args = TYPE_ARG_TYPES (type); + if (args != NULL) + { + if ((args[1] != NULL && args[1]->code != TYPE_CODE_VOID) || + (args[2] != NULL)) + { + fprintf_filtered (stream, "("); + } + if (args[1] == NULL) + { + fprintf_filtered (stream, "..."); + } + else + { + for (i = 1; + args[i] != NULL && args[i]->code != TYPE_CODE_VOID; + i++) + { + pascal_print_type (args[i], "", stream, -1, 0); + if (args[i + 1] == NULL) + { + fprintf_filtered (stream, "..."); + } + else if (args[i + 1]->code != TYPE_CODE_VOID) + { + fprintf_filtered (stream, ","); + wrap_here (" "); + } + } + } + if ((args[1] != NULL && args[1]->code != TYPE_CODE_VOID) || + (args[2] != NULL)) + { + fprintf_filtered (stream, ")"); + } + } +} + +static void +pascal_print_func_args (struct type *type, struct ui_file *stream) +{ + int i, len = TYPE_NFIELDS (type); + if (len) + { + fprintf_filtered (stream, "("); + } + for (i = 0; i < len; i++) + { + if (i > 0) + { + fputs_filtered (", ", stream); + wrap_here (" "); + } + /* can we find if it is a var parameter ?? + if ( TYPE_FIELD(type, i) == ) + { + fprintf_filtered (stream, "var "); + } */ + pascal_print_type (TYPE_FIELD_TYPE (type, i), "" /* TYPE_FIELD_NAME seems invalid ! */ + ,stream, -1, 0); + } + if (len) + { + fprintf_filtered (stream, ")"); + } +} + +/* Print any array sizes, function arguments or close parentheses + needed after the variable name (to describe its type). + Args work like pascal_type_print_varspec_prefix. */ + +static void +pascal_type_print_varspec_suffix (type, stream, show, passed_a_ptr, demangled_args) + struct type *type; + struct ui_file *stream; + int show; + int passed_a_ptr; + int demangled_args; +{ + if (type == 0) + return; + + if (TYPE_NAME (type) && show <= 0) + return; + + QUIT; + + switch (TYPE_CODE (type)) + { + case TYPE_CODE_ARRAY: + if (passed_a_ptr) + fprintf_filtered (stream, ")"); + break; + + case TYPE_CODE_MEMBER: + if (passed_a_ptr) + fprintf_filtered (stream, ")"); + pascal_type_print_varspec_suffix (TYPE_TARGET_TYPE (type), stream, 0, 0, 0); + break; + + case TYPE_CODE_METHOD: + if (passed_a_ptr) + fprintf_filtered (stream, ")"); + pascal_type_print_method_args ("", + "", + stream); + /* pascal_type_print_args (type, stream); */ + if (TYPE_CODE (TYPE_TARGET_TYPE (type)) != TYPE_CODE_VOID) + { + fprintf_filtered (stream, " : "); + pascal_type_print_varspec_prefix (TYPE_TARGET_TYPE (type), stream, 0, 0); + pascal_type_print_base (TYPE_TARGET_TYPE (type), stream, show, 0); + pascal_type_print_varspec_suffix (TYPE_TARGET_TYPE (type), stream, 0, + passed_a_ptr, 0); + } + break; + + case TYPE_CODE_PTR: + case TYPE_CODE_REF: + pascal_type_print_varspec_suffix (TYPE_TARGET_TYPE (type), stream, 0, 1, 0); + break; + + case TYPE_CODE_FUNC: + if (passed_a_ptr) + fprintf_filtered (stream, ")"); + if (!demangled_args) + pascal_print_func_args (type, stream); + if (TYPE_CODE (TYPE_TARGET_TYPE (type)) != TYPE_CODE_VOID) + { + fprintf_filtered (stream, " : "); + pascal_type_print_varspec_prefix (TYPE_TARGET_TYPE (type), stream, 0, 0); + pascal_type_print_base (TYPE_TARGET_TYPE (type), stream, show, 0); + pascal_type_print_varspec_suffix (TYPE_TARGET_TYPE (type), stream, 0, + passed_a_ptr, 0); + } + break; + + case TYPE_CODE_UNDEF: + case TYPE_CODE_STRUCT: + case TYPE_CODE_UNION: + case TYPE_CODE_ENUM: + case TYPE_CODE_INT: + case TYPE_CODE_FLT: + case TYPE_CODE_VOID: + case TYPE_CODE_ERROR: + case TYPE_CODE_CHAR: + case TYPE_CODE_BOOL: + case TYPE_CODE_SET: + case TYPE_CODE_RANGE: + case TYPE_CODE_STRING: + case TYPE_CODE_BITSTRING: + case TYPE_CODE_COMPLEX: + case TYPE_CODE_TYPEDEF: + case TYPE_CODE_TEMPLATE: + /* These types do not need a suffix. They are listed so that + gcc -Wall will report types that may not have been considered. */ + break; + default: + error ("type not handled in pascal_type_print_varspec_suffix()"); + break; + } +} + +/* Print the name of the type (or the ultimate pointer target, + function value or array element), or the description of a + structure or union. + + SHOW positive means print details about the type (e.g. enum values), + and print structure elements passing SHOW - 1 for show. + SHOW negative means just print the type name or struct tag if there is one. + If there is no name, print something sensible but concise like + "struct {...}". + SHOW zero means just print the type name or struct tag if there is one. + If there is no name, print something sensible but not as concise like + "struct {int x; int y;}". + + LEVEL is the number of spaces to indent by. + We increase it for some recursive calls. */ + +void +pascal_type_print_base (type, stream, show, level) + struct type *type; + struct ui_file *stream; + int show; + int level; +{ + register int i; + register int len; + register int lastval; + enum + { + s_none, s_public, s_private, s_protected + } + section_type; + QUIT; + + wrap_here (" "); + if (type == NULL) + { + fputs_filtered ("<type unknown>", stream); + return; + } + + /* void pointer */ + if ((TYPE_CODE (type) == TYPE_CODE_PTR) && (TYPE_CODE (TYPE_TARGET_TYPE (type)) == TYPE_CODE_VOID)) + { + fprintf_filtered (stream, + TYPE_NAME (type) ? TYPE_NAME (type) : "pointer"); + return; + } + /* When SHOW is zero or less, and there is a valid type name, then always + just print the type name directly from the type. */ + + if (show <= 0 + && TYPE_NAME (type) != NULL) + { + fputs_filtered (TYPE_NAME (type), stream); + return; + } + + CHECK_TYPEDEF (type); + + switch (TYPE_CODE (type)) + { + case TYPE_CODE_TYPEDEF: + case TYPE_CODE_PTR: + case TYPE_CODE_MEMBER: + case TYPE_CODE_REF: + /* case TYPE_CODE_FUNC: + case TYPE_CODE_METHOD: */ + pascal_type_print_base (TYPE_TARGET_TYPE (type), stream, show, level); + break; + + case TYPE_CODE_ARRAY: + /* pascal_type_print_varspec_prefix (TYPE_TARGET_TYPE (type), stream, 0, 0); + pascal_type_print_base (TYPE_TARGET_TYPE (type), stream, show, level); + pascal_type_print_varspec_suffix (TYPE_TARGET_TYPE (type), stream, 0, 0, 0); */ + pascal_print_type (TYPE_TARGET_TYPE (type), NULL, stream, 0, 0); + break; + + case TYPE_CODE_FUNC: + case TYPE_CODE_METHOD: + /* + pascal_type_print_base (TYPE_TARGET_TYPE (type), stream, show, level); + only after args !! */ + break; + case TYPE_CODE_STRUCT: + if (TYPE_TAG_NAME (type) != NULL) + { + fputs_filtered (TYPE_TAG_NAME (type), stream); + fputs_filtered (" = ", stream); + } + if (HAVE_CPLUS_STRUCT (type)) + { + fprintf_filtered (stream, "class "); + } + else + { + fprintf_filtered (stream, "record "); + } + goto struct_union; + + case TYPE_CODE_UNION: + if (TYPE_TAG_NAME (type) != NULL) + { + fputs_filtered (TYPE_TAG_NAME (type), stream); + fputs_filtered (" = ", stream); + } + fprintf_filtered (stream, "case <?> of "); + + struct_union: + wrap_here (" "); + if (show < 0) + { + /* If we just printed a tag name, no need to print anything else. */ + if (TYPE_TAG_NAME (type) == NULL) + fprintf_filtered (stream, "{...}"); + } + else if (show > 0 || TYPE_TAG_NAME (type) == NULL) + { + pascal_type_print_derivation_info (stream, type); + + fprintf_filtered (stream, "\n"); + if ((TYPE_NFIELDS (type) == 0) && (TYPE_NFN_FIELDS (type) == 0)) + { + if (TYPE_FLAGS (type) & TYPE_FLAG_STUB) + fprintfi_filtered (level + 4, stream, "<incomplete type>\n"); + else + fprintfi_filtered (level + 4, stream, "<no data fields>\n"); + } + + /* Start off with no specific section type, so we can print + one for the first field we find, and use that section type + thereafter until we find another type. */ + + section_type = s_none; + + /* If there is a base class for this type, + do not print the field that it occupies. */ + + len = TYPE_NFIELDS (type); + for (i = TYPE_N_BASECLASSES (type); i < len; i++) + { + QUIT; + /* Don't print out virtual function table. */ + if (STREQN (TYPE_FIELD_NAME (type, i), "_vptr", 5) + && is_cplus_marker ((TYPE_FIELD_NAME (type, i))[5])) + continue; + + /* If this is a pascal object or class we can print the + various section labels. */ + + if (HAVE_CPLUS_STRUCT (type)) + { + if (TYPE_FIELD_PROTECTED (type, i)) + { + if (section_type != s_protected) + { + section_type = s_protected; + fprintfi_filtered (level + 2, stream, + "protected\n"); + } + } + else if (TYPE_FIELD_PRIVATE (type, i)) + { + if (section_type != s_private) + { + section_type = s_private; + fprintfi_filtered (level + 2, stream, "private\n"); + } + } + else + { + if (section_type != s_public) + { + section_type = s_public; + fprintfi_filtered (level + 2, stream, "public\n"); + } + } + } + + print_spaces_filtered (level + 4, stream); + if (TYPE_FIELD_STATIC (type, i)) + { + fprintf_filtered (stream, "static "); + } + pascal_print_type (TYPE_FIELD_TYPE (type, i), + TYPE_FIELD_NAME (type, i), + stream, show - 1, level + 4); + if (!TYPE_FIELD_STATIC (type, i) + && TYPE_FIELD_PACKED (type, i)) + { + /* It is a bitfield. This code does not attempt + to look at the bitpos and reconstruct filler, + unnamed fields. This would lead to misleading + results if the compiler does not put out fields + for such things (I don't know what it does). */ + fprintf_filtered (stream, " : %d", + TYPE_FIELD_BITSIZE (type, i)); + } + fprintf_filtered (stream, ";\n"); + } + + /* If there are both fields and methods, put a space between. */ + len = TYPE_NFN_FIELDS (type); + if (len && section_type != s_none) + fprintf_filtered (stream, "\n"); + + /* Pbject pascal: print out the methods */ + + for (i = 0; i < len; i++) + { + struct fn_field *f = TYPE_FN_FIELDLIST1 (type, i); + int j, len2 = TYPE_FN_FIELDLIST_LENGTH (type, i); + char *method_name = TYPE_FN_FIELDLIST_NAME (type, i); + char *name = type_name_no_tag (type); + /* this is GNU C++ specific + how can we know constructor/destructor? + It might work for GNU pascal */ + for (j = 0; j < len2; j++) + { + char *physname = TYPE_FN_FIELD_PHYSNAME (f, j); + + int is_constructor = STREQN (physname, "__ct__", 6); + int is_destructor = STREQN (physname, "__dt__", 6); + + QUIT; + if (TYPE_FN_FIELD_PROTECTED (f, j)) + { + if (section_type != s_protected) + { + section_type = s_protected; + fprintfi_filtered (level + 2, stream, + "protected\n"); + } + } + else if (TYPE_FN_FIELD_PRIVATE (f, j)) + { + if (section_type != s_private) + { + section_type = s_private; + fprintfi_filtered (level + 2, stream, "private\n"); + } + } + else + { + if (section_type != s_public) + { + section_type = s_public; + fprintfi_filtered (level + 2, stream, "public\n"); + } + } + + print_spaces_filtered (level + 4, stream); + if (TYPE_FN_FIELD_STATIC_P (f, j)) + fprintf_filtered (stream, "static "); + if (TYPE_TARGET_TYPE (TYPE_FN_FIELD_TYPE (f, j)) == 0) + { + /* Keep GDB from crashing here. */ + fprintf_filtered (stream, "<undefined type> %s;\n", + TYPE_FN_FIELD_PHYSNAME (f, j)); + break; + } + + if (is_constructor) + { + fprintf_filtered (stream, "constructor "); + } + else if (is_destructor) + { + fprintf_filtered (stream, "destructor "); + } + else if (TYPE_TARGET_TYPE (TYPE_FN_FIELD_TYPE (f, j)) != 0 && + TYPE_CODE (TYPE_TARGET_TYPE (TYPE_FN_FIELD_TYPE (f, j))) != TYPE_CODE_VOID) + { + fprintf_filtered (stream, "function "); + } + else + { + fprintf_filtered (stream, "procedure "); + } + /* this does not work, no idea why !! */ + + pascal_type_print_method_args (physname, + method_name, + stream); + + if (TYPE_TARGET_TYPE (TYPE_FN_FIELD_TYPE (f, j)) != 0 && + TYPE_CODE (TYPE_TARGET_TYPE (TYPE_FN_FIELD_TYPE (f, j))) != TYPE_CODE_VOID) + { + fputs_filtered (" : ", stream); + type_print (TYPE_TARGET_TYPE (TYPE_FN_FIELD_TYPE (f, j)), + "", stream, -1); + } + if (TYPE_FN_FIELD_VIRTUAL_P (f, j)) + fprintf_filtered (stream, "; virtual"); + + fprintf_filtered (stream, ";\n"); + } + } + fprintfi_filtered (level, stream, "end"); + } + break; + + case TYPE_CODE_ENUM: + if (TYPE_TAG_NAME (type) != NULL) + { + fputs_filtered (TYPE_TAG_NAME (type), stream); + if (show > 0) + fputs_filtered (" ", stream); + } + /* enum is just defined by + type enume_name = (enum_member1,enum_member2,...) */ + fprintf_filtered (stream, " = "); + wrap_here (" "); + if (show < 0) + { + /* If we just printed a tag name, no need to print anything else. */ + if (TYPE_TAG_NAME (type) == NULL) + fprintf_filtered (stream, "(...)"); + } + else if (show > 0 || TYPE_TAG_NAME (type) == NULL) + { + fprintf_filtered (stream, "("); + len = TYPE_NFIELDS (type); + lastval = 0; + for (i = 0; i < len; i++) + { + QUIT; + if (i) + fprintf_filtered (stream, ", "); + wrap_here (" "); + fputs_filtered (TYPE_FIELD_NAME (type, i), stream); + if (lastval != TYPE_FIELD_BITPOS (type, i)) + { + fprintf_filtered (stream, " := %d", TYPE_FIELD_BITPOS (type, i)); + lastval = TYPE_FIELD_BITPOS (type, i); + } + lastval++; + } + fprintf_filtered (stream, ")"); + } + break; + + case TYPE_CODE_VOID: + fprintf_filtered (stream, "void"); + break; + + case TYPE_CODE_UNDEF: + fprintf_filtered (stream, "record <unknown>"); + break; + + case TYPE_CODE_ERROR: + fprintf_filtered (stream, "<unknown type>"); + break; + + /* this probably does not work for enums */ + case TYPE_CODE_RANGE: + { + struct type *target = TYPE_TARGET_TYPE (type); + if (target == NULL) + target = builtin_type_long; + print_type_scalar (target, TYPE_LOW_BOUND (type), stream); + fputs_filtered ("..", stream); + print_type_scalar (target, TYPE_HIGH_BOUND (type), stream); + } + break; + + case TYPE_CODE_SET: + fputs_filtered ("set of ", stream); + pascal_print_type (TYPE_INDEX_TYPE (type), "", stream, + show - 1, level); + break; + + default: + /* Handle types not explicitly handled by the other cases, + such as fundamental types. For these, just print whatever + the type name is, as recorded in the type itself. If there + is no type name, then complain. */ + if (TYPE_NAME (type) != NULL) + { + fputs_filtered (TYPE_NAME (type), stream); + } + else + { + /* At least for dump_symtab, it is important that this not be + an error (). */ + fprintf_filtered (stream, "<invalid unnamed pascal type code %d>", + TYPE_CODE (type)); + } + break; + } +} diff --git a/gdb/p-valprint.c b/gdb/p-valprint.c new file mode 100644 index 0000000..b18e7cf --- /dev/null +++ b/gdb/p-valprint.c @@ -0,0 +1,1145 @@ +/* Support for printing Pascal values for GDB, the GNU debugger. + Copyright 2000 + Free Software Foundation, Inc. + + This file is part of GDB. + + This program is free software; you can redistribute it and/or modify + it under the terms of the GNU General Public License as published by + the Free Software Foundation; either version 2 of the License, or + (at your option) any later version. + + This program is distributed in the hope that it will be useful, + but WITHOUT ANY WARRANTY; without even the implied warranty of + MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + GNU General Public License for more details. + + You should have received a copy of the GNU General Public License + along with this program; if not, write to the Free Software + Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */ + +/* This file is derived from c-valprint.c */ + +#include "defs.h" +#include "obstack.h" +#include "symtab.h" +#include "gdbtypes.h" +#include "expression.h" +#include "value.h" +#include "command.h" +#include "gdbcmd.h" +#include "gdbcore.h" +#include "demangle.h" +#include "valprint.h" +#include "language.h" +#include "target.h" +#include "annotate.h" +#include "p-lang.h" + + + + +/* Print data of type TYPE located at VALADDR (within GDB), which came from + the inferior at address ADDRESS, onto stdio stream STREAM according to + FORMAT (a letter or 0 for natural format). The data at VALADDR is in + target byte order. + + If the data are a string pointer, returns the number of string characters + printed. + + If DEREF_REF is nonzero, then dereference references, otherwise just print + them like pointers. + + The PRETTY parameter controls prettyprinting. */ + + +int +pascal_val_print (type, valaddr, embedded_offset, address, stream, format, deref_ref, recurse, + pretty) + struct type *type; + char *valaddr; + int embedded_offset; + CORE_ADDR address; + struct ui_file *stream; + int format; + int deref_ref; + int recurse; + enum val_prettyprint pretty; +{ + register unsigned int i = 0; /* Number of characters printed */ + unsigned len; + struct type *elttype; + unsigned eltlen; + LONGEST val; + CORE_ADDR addr; + + CHECK_TYPEDEF (type); + switch (TYPE_CODE (type)) + { + case TYPE_CODE_ARRAY: + if (TYPE_LENGTH (type) > 0 && TYPE_LENGTH (TYPE_TARGET_TYPE (type)) > 0) + { + elttype = check_typedef (TYPE_TARGET_TYPE (type)); + eltlen = TYPE_LENGTH (elttype); + len = TYPE_LENGTH (type) / eltlen; + if (prettyprint_arrays) + { + print_spaces_filtered (2 + 2 * recurse, stream); + } + /* For an array of chars, print with string syntax. */ + if (eltlen == 1 && + ((TYPE_CODE (elttype) == TYPE_CODE_INT) + || ((current_language->la_language == language_m2) + && (TYPE_CODE (elttype) == TYPE_CODE_CHAR))) + && (format == 0 || format == 's')) + { + /* If requested, look for the first null char and only print + elements up to it. */ + if (stop_print_at_null) + { + unsigned int temp_len; + + /* Look for a NULL char. */ + for (temp_len = 0; + (valaddr + embedded_offset)[temp_len] + && temp_len < len && temp_len < print_max; + temp_len++); + len = temp_len; + } + + LA_PRINT_STRING (stream, valaddr + embedded_offset, len, 1, 0); + i = len; + } + else + { + fprintf_filtered (stream, "{"); + /* If this is a virtual function table, print the 0th + entry specially, and the rest of the members normally. */ + if (pascal_object_is_vtbl_ptr_type (elttype)) + { + i = 1; + fprintf_filtered (stream, "%d vtable entries", len - 1); + } + else + { + i = 0; + } + val_print_array_elements (type, valaddr + embedded_offset, address, stream, + format, deref_ref, recurse, pretty, i); + fprintf_filtered (stream, "}"); + } + break; + } + /* Array of unspecified length: treat like pointer to first elt. */ + addr = address; + goto print_unpacked_pointer; + + case TYPE_CODE_PTR: + if (format && format != 's') + { + print_scalar_formatted (valaddr + embedded_offset, type, format, 0, stream); + break; + } + if (vtblprint && pascal_object_is_vtbl_ptr_type (type)) + { + /* Print the unmangled name if desired. */ + /* Print vtable entry - we only get here if we ARE using + -fvtable_thunks. (Otherwise, look under TYPE_CODE_STRUCT.) */ + print_address_demangle (extract_address (valaddr + embedded_offset, TYPE_LENGTH (type)), + stream, demangle); + break; + } + elttype = check_typedef (TYPE_TARGET_TYPE (type)); + if (TYPE_CODE (elttype) == TYPE_CODE_METHOD) + { + pascal_object_print_class_method (valaddr + embedded_offset, type, stream); + } + else if (TYPE_CODE (elttype) == TYPE_CODE_MEMBER) + { + pascal_object_print_class_member (valaddr + embedded_offset, + TYPE_DOMAIN_TYPE (TYPE_TARGET_TYPE (type)), + stream, "&"); + } + else + { + addr = unpack_pointer (type, valaddr + embedded_offset); + print_unpacked_pointer: + elttype = check_typedef (TYPE_TARGET_TYPE (type)); + + if (TYPE_CODE (elttype) == TYPE_CODE_FUNC) + { + /* Try to print what function it points to. */ + print_address_demangle (addr, stream, demangle); + /* Return value is irrelevant except for string pointers. */ + return (0); + } + + if (addressprint && format != 's') + { + print_address_numeric (addr, 1, stream); + } + + /* For a pointer to char or unsigned char, also print the string + pointed to, unless pointer is null. */ + if (TYPE_LENGTH (elttype) == 1 + && TYPE_CODE (elttype) == TYPE_CODE_INT + && (format == 0 || format == 's') + && addr != 0) + { + /* no wide string yet */ + i = val_print_string (addr, -1, 1, stream); + } + /* also for pointers to pascal strings */ + /* Note: this is Free Pascal specific: + as GDB does not recognize stabs pascal strings + Pascal strings are mapped to records + with lowercase names PM */ + /* I don't know what GPC does :( PM */ + if (TYPE_CODE (elttype) == TYPE_CODE_STRUCT && + TYPE_NFIELDS (elttype) == 2 && + strcmp (TYPE_FIELDS (elttype)[0].name, "length") == 0 && + strcmp (TYPE_FIELDS (elttype)[1].name, "st") == 0 && + addr != 0) + { + char bytelength; + read_memory (addr, &bytelength, 1); + i = val_print_string (addr + 1, bytelength, 1, stream); + } + else if (pascal_object_is_vtbl_member (type)) + { + /* print vtbl's nicely */ + CORE_ADDR vt_address = unpack_pointer (type, valaddr + embedded_offset); + + struct minimal_symbol *msymbol = + lookup_minimal_symbol_by_pc (vt_address); + if ((msymbol != NULL) && + (vt_address == SYMBOL_VALUE_ADDRESS (msymbol))) + { + fputs_filtered (" <", stream); + fputs_filtered (SYMBOL_SOURCE_NAME (msymbol), stream); + fputs_filtered (">", stream); + } + if (vt_address && vtblprint) + { + value_ptr vt_val; + struct symbol *wsym = (struct symbol *) NULL; + struct type *wtype; + struct symtab *s; + struct block *block = (struct block *) NULL; + int is_this_fld; + + if (msymbol != NULL) + wsym = lookup_symbol (SYMBOL_NAME (msymbol), block, + VAR_NAMESPACE, &is_this_fld, &s); + + if (wsym) + { + wtype = SYMBOL_TYPE (wsym); + } + else + { + wtype = TYPE_TARGET_TYPE (type); + } + vt_val = value_at (wtype, vt_address, NULL); + val_print (VALUE_TYPE (vt_val), VALUE_CONTENTS (vt_val), 0, + VALUE_ADDRESS (vt_val), stream, format, + deref_ref, recurse + 1, pretty); + if (pretty) + { + fprintf_filtered (stream, "\n"); + print_spaces_filtered (2 + 2 * recurse, stream); + } + } + } + + /* Return number of characters printed, including the terminating + '\0' if we reached the end. val_print_string takes care including + the terminating '\0' if necessary. */ + return i; + } + break; + + case TYPE_CODE_MEMBER: + error ("not implemented: member type in pascal_val_print"); + break; + + case TYPE_CODE_REF: + elttype = check_typedef (TYPE_TARGET_TYPE (type)); + if (TYPE_CODE (elttype) == TYPE_CODE_MEMBER) + { + pascal_object_print_class_member (valaddr + embedded_offset, + TYPE_DOMAIN_TYPE (elttype), + stream, ""); + break; + } + if (addressprint) + { + fprintf_filtered (stream, "@"); + print_address_numeric + (extract_address (valaddr + embedded_offset, + TARGET_PTR_BIT / HOST_CHAR_BIT), 1, stream); + if (deref_ref) + fputs_filtered (": ", stream); + } + /* De-reference the reference. */ + if (deref_ref) + { + if (TYPE_CODE (elttype) != TYPE_CODE_UNDEF) + { + value_ptr deref_val = + value_at + (TYPE_TARGET_TYPE (type), + unpack_pointer (lookup_pointer_type (builtin_type_void), + valaddr + embedded_offset), + NULL); + val_print (VALUE_TYPE (deref_val), + VALUE_CONTENTS (deref_val), 0, + VALUE_ADDRESS (deref_val), stream, format, + deref_ref, recurse + 1, pretty); + } + else + fputs_filtered ("???", stream); + } + break; + + case TYPE_CODE_UNION: + if (recurse && !unionprint) + { + fprintf_filtered (stream, "{...}"); + break; + } + /* Fall through. */ + case TYPE_CODE_STRUCT: + if (vtblprint && pascal_object_is_vtbl_ptr_type (type)) + { + /* Print the unmangled name if desired. */ + /* Print vtable entry - we only get here if NOT using + -fvtable_thunks. (Otherwise, look under TYPE_CODE_PTR.) */ + print_address_demangle (extract_address ( + valaddr + embedded_offset + TYPE_FIELD_BITPOS (type, VTBL_FNADDR_OFFSET) / 8, + TYPE_LENGTH (TYPE_FIELD_TYPE (type, VTBL_FNADDR_OFFSET))), + stream, demangle); + } + else + { + if ((TYPE_NFIELDS (type) == 2) && + (strcmp (TYPE_FIELDS (type)[0].name, "length") == 0) && + (strcmp (TYPE_FIELDS (type)[1].name, "st") == 0)) + { + len = (*(valaddr + embedded_offset)) & 0xff; + LA_PRINT_STRING (stream, valaddr + embedded_offset + 1, len, /* width ?? */ 0, 0); + } + else + pascal_object_print_value_fields (type, valaddr + embedded_offset, address, stream, format, + recurse, pretty, NULL, 0); + } + break; + + case TYPE_CODE_ENUM: + if (format) + { + print_scalar_formatted (valaddr + embedded_offset, type, format, 0, stream); + break; + } + len = TYPE_NFIELDS (type); + val = unpack_long (type, valaddr + embedded_offset); + for (i = 0; i < len; i++) + { + QUIT; + if (val == TYPE_FIELD_BITPOS (type, i)) + { + break; + } + } + if (i < len) + { + fputs_filtered (TYPE_FIELD_NAME (type, i), stream); + } + else + { + print_longest (stream, 'd', 0, val); + } + break; + + case TYPE_CODE_FUNC: + if (format) + { + print_scalar_formatted (valaddr + embedded_offset, type, format, 0, stream); + break; + } + /* FIXME, we should consider, at least for ANSI C language, eliminating + the distinction made between FUNCs and POINTERs to FUNCs. */ + fprintf_filtered (stream, "{"); + type_print (type, "", stream, -1); + fprintf_filtered (stream, "} "); + /* Try to print what function it points to, and its address. */ + print_address_demangle (address, stream, demangle); + break; + + case TYPE_CODE_BOOL: + format = format ? format : output_format; + if (format) + print_scalar_formatted (valaddr + embedded_offset, type, format, 0, stream); + else + { + val = unpack_long (type, valaddr + embedded_offset); + if (val == 0) + fputs_filtered ("false", stream); + else if (val == 1) + fputs_filtered ("true", stream); + else + { + fputs_filtered ("true (", stream); + fprintf_filtered (stream, "%ld)", (long int) val); + } + } + break; + + case TYPE_CODE_RANGE: + /* FIXME: create_range_type does not set the unsigned bit in a + range type (I think it probably should copy it from the target + type), so we won't print values which are too large to + fit in a signed integer correctly. */ + /* FIXME: Doesn't handle ranges of enums correctly. (Can't just + print with the target type, though, because the size of our type + and the target type might differ). */ + /* FALLTHROUGH */ + + case TYPE_CODE_INT: + format = format ? format : output_format; + if (format) + { + print_scalar_formatted (valaddr + embedded_offset, type, format, 0, stream); + } + else + { + val_print_type_code_int (type, valaddr + embedded_offset, stream); + } + break; + + case TYPE_CODE_CHAR: + format = format ? format : output_format; + if (format) + { + print_scalar_formatted (valaddr + embedded_offset, type, format, 0, stream); + } + else + { + val = unpack_long (type, valaddr + embedded_offset); + if (TYPE_UNSIGNED (type)) + fprintf_filtered (stream, "%u", (unsigned int) val); + else + fprintf_filtered (stream, "%d", (int) val); + fputs_filtered (" ", stream); + LA_PRINT_CHAR ((unsigned char) val, stream); + } + break; + + case TYPE_CODE_FLT: + if (format) + { + print_scalar_formatted (valaddr + embedded_offset, type, format, 0, stream); + } + else + { + print_floating (valaddr + embedded_offset, type, stream); + } + break; + + case TYPE_CODE_BITSTRING: + case TYPE_CODE_SET: + elttype = TYPE_INDEX_TYPE (type); + CHECK_TYPEDEF (elttype); + if (TYPE_FLAGS (elttype) & TYPE_FLAG_STUB) + { + fprintf_filtered (stream, "<incomplete type>"); + gdb_flush (stream); + break; + } + else + { + struct type *range = elttype; + LONGEST low_bound, high_bound; + int i; + int is_bitstring = TYPE_CODE (type) == TYPE_CODE_BITSTRING; + int need_comma = 0; + + if (is_bitstring) + fputs_filtered ("B'", stream); + else + fputs_filtered ("[", stream); + + i = get_discrete_bounds (range, &low_bound, &high_bound); + maybe_bad_bstring: + if (i < 0) + { + fputs_filtered ("<error value>", stream); + goto done; + } + + for (i = low_bound; i <= high_bound; i++) + { + int element = value_bit_index (type, valaddr + embedded_offset, i); + if (element < 0) + { + i = element; + goto maybe_bad_bstring; + } + if (is_bitstring) + fprintf_filtered (stream, "%d", element); + else if (element) + { + if (need_comma) + fputs_filtered (", ", stream); + print_type_scalar (range, i, stream); + need_comma = 1; + + if (i + 1 <= high_bound && value_bit_index (type, valaddr + embedded_offset, ++i)) + { + int j = i; + fputs_filtered ("..", stream); + while (i + 1 <= high_bound + && value_bit_index (type, valaddr + embedded_offset, ++i)) + j = i; + print_type_scalar (range, j, stream); + } + } + } + done: + if (is_bitstring) + fputs_filtered ("'", stream); + else + fputs_filtered ("]", stream); + } + break; + + case TYPE_CODE_VOID: + fprintf_filtered (stream, "void"); + break; + + case TYPE_CODE_ERROR: + fprintf_filtered (stream, "<error type>"); + break; + + case TYPE_CODE_UNDEF: + /* This happens (without TYPE_FLAG_STUB set) on systems which don't use + dbx xrefs (NO_DBX_XREFS in gcc) if a file has a "struct foo *bar" + and no complete type for struct foo in that file. */ + fprintf_filtered (stream, "<incomplete type>"); + break; + + default: + error ("Invalid pascal type code %d in symbol table.", TYPE_CODE (type)); + } + gdb_flush (stream); + return (0); +} + +int +pascal_value_print (val, stream, format, pretty) + value_ptr val; + struct ui_file *stream; + int format; + enum val_prettyprint pretty; +{ + struct type *type = VALUE_TYPE (val); + + /* If it is a pointer, indicate what it points to. + + Print type also if it is a reference. + + Object pascal: if it is a member pointer, we will take care + of that when we print it. */ + if (TYPE_CODE (type) == TYPE_CODE_PTR || + TYPE_CODE (type) == TYPE_CODE_REF) + { + /* Hack: remove (char *) for char strings. Their + type is indicated by the quoted string anyway. */ + if (TYPE_CODE (type) == TYPE_CODE_PTR && + TYPE_NAME (type) == NULL && + TYPE_NAME (TYPE_TARGET_TYPE (type)) != NULL && + STREQ (TYPE_NAME (TYPE_TARGET_TYPE (type)), "char")) + { + /* Print nothing */ + } + else + { + fprintf_filtered (stream, "("); + type_print (type, "", stream, -1); + fprintf_filtered (stream, ") "); + } + } + return val_print (type, VALUE_CONTENTS (val), VALUE_EMBEDDED_OFFSET (val), + VALUE_ADDRESS (val) + VALUE_OFFSET (val), + stream, format, 1, 0, pretty); +} + + +/****************************************************************************** + Inserted from cp-valprint +******************************************************************************/ + +extern int vtblprint; /* Controls printing of vtbl's */ +extern int objectprint; /* Controls looking up an object's derived type + using what we find in its vtables. */ +static int pascal_static_field_print; /* Controls printing of static fields. */ + +static struct obstack dont_print_vb_obstack; +static struct obstack dont_print_statmem_obstack; + +static void + pascal_object_print_static_field (struct type *, value_ptr, struct ui_file *, int, int, + enum val_prettyprint); + +static void + pascal_object_print_value (struct type *, char *, CORE_ADDR, struct ui_file *, + int, int, enum val_prettyprint, struct type **); + +void +pascal_object_print_class_method (valaddr, type, stream) + char *valaddr; + struct type *type; + struct ui_file *stream; +{ + struct type *domain; + struct fn_field *f = NULL; + int j = 0; + int len2; + int offset; + char *kind = ""; + CORE_ADDR addr; + struct symbol *sym; + unsigned len; + unsigned int i; + struct type *target_type = check_typedef (TYPE_TARGET_TYPE (type)); + + domain = TYPE_DOMAIN_TYPE (target_type); + if (domain == (struct type *) NULL) + { + fprintf_filtered (stream, "<unknown>"); + return; + } + addr = unpack_pointer (lookup_pointer_type (builtin_type_void), valaddr); + if (METHOD_PTR_IS_VIRTUAL (addr)) + { + offset = METHOD_PTR_TO_VOFFSET (addr); + len = TYPE_NFN_FIELDS (domain); + for (i = 0; i < len; i++) + { + f = TYPE_FN_FIELDLIST1 (domain, i); + len2 = TYPE_FN_FIELDLIST_LENGTH (domain, i); + + for (j = 0; j < len2; j++) + { + QUIT; + if (TYPE_FN_FIELD_VOFFSET (f, j) == offset) + { + if (TYPE_FN_FIELD_STUB (f, j)) + check_stub_method (domain, i, j); + kind = "virtual "; + goto common; + } + } + } + } + else + { + sym = find_pc_function (addr); + if (sym == 0) + { + error ("invalid pointer to member function"); + } + len = TYPE_NFN_FIELDS (domain); + for (i = 0; i < len; i++) + { + f = TYPE_FN_FIELDLIST1 (domain, i); + len2 = TYPE_FN_FIELDLIST_LENGTH (domain, i); + + for (j = 0; j < len2; j++) + { + QUIT; + if (TYPE_FN_FIELD_STUB (f, j)) + check_stub_method (domain, i, j); + if (STREQ (SYMBOL_NAME (sym), TYPE_FN_FIELD_PHYSNAME (f, j))) + { + goto common; + } + } + } + } +common: + if (i < len) + { + char *demangled_name; + + fprintf_filtered (stream, "&"); + fprintf_filtered (stream, kind); + demangled_name = cplus_demangle (TYPE_FN_FIELD_PHYSNAME (f, j), + DMGL_ANSI | DMGL_PARAMS); + if (demangled_name == NULL) + fprintf_filtered (stream, "<badly mangled name %s>", + TYPE_FN_FIELD_PHYSNAME (f, j)); + else + { + fputs_filtered (demangled_name, stream); + free (demangled_name); + } + } + else + { + fprintf_filtered (stream, "("); + type_print (type, "", stream, -1); + fprintf_filtered (stream, ") %d", (int) addr >> 3); + } +} + +/* It was changed to this after 2.4.5. */ +const char pascal_vtbl_ptr_name[] = +{'_', '_', 'v', 't', 'b', 'l', '_', 'p', 't', 'r', '_', 't', 'y', 'p', 'e', 0}; + +/* Return truth value for assertion that TYPE is of the type + "pointer to virtual function". */ + +int +pascal_object_is_vtbl_ptr_type (type) + struct type *type; +{ + char *typename = type_name_no_tag (type); + + return (typename != NULL + && (STREQ (typename, pascal_vtbl_ptr_name))); +} + +/* Return truth value for the assertion that TYPE is of the type + "pointer to virtual function table". */ + +int +pascal_object_is_vtbl_member (type) + struct type *type; +{ + if (TYPE_CODE (type) == TYPE_CODE_PTR) + { + type = TYPE_TARGET_TYPE (type); + if (TYPE_CODE (type) == TYPE_CODE_ARRAY) + { + type = TYPE_TARGET_TYPE (type); + if (TYPE_CODE (type) == TYPE_CODE_STRUCT /* if not using thunks */ + || TYPE_CODE (type) == TYPE_CODE_PTR) /* if using thunks */ + { + /* Virtual functions tables are full of pointers + to virtual functions. */ + return pascal_object_is_vtbl_ptr_type (type); + } + } + } + return 0; +} + +/* Mutually recursive subroutines of pascal_object_print_value and c_val_print to + print out a structure's fields: pascal_object_print_value_fields and pascal_object_print_value. + + TYPE, VALADDR, ADDRESS, STREAM, RECURSE, and PRETTY have the + same meanings as in pascal_object_print_value and c_val_print. + + DONT_PRINT is an array of baseclass types that we + should not print, or zero if called from top level. */ + +void +pascal_object_print_value_fields (type, valaddr, address, stream, format, recurse, pretty, + dont_print_vb, dont_print_statmem) + struct type *type; + char *valaddr; + CORE_ADDR address; + struct ui_file *stream; + int format; + int recurse; + enum val_prettyprint pretty; + struct type **dont_print_vb; + int dont_print_statmem; +{ + int i, len, n_baseclasses; + struct obstack tmp_obstack; + char *last_dont_print = obstack_next_free (&dont_print_statmem_obstack); + + CHECK_TYPEDEF (type); + + fprintf_filtered (stream, "{"); + len = TYPE_NFIELDS (type); + n_baseclasses = TYPE_N_BASECLASSES (type); + + /* Print out baseclasses such that we don't print + duplicates of virtual baseclasses. */ + if (n_baseclasses > 0) + pascal_object_print_value (type, valaddr, address, stream, + format, recurse + 1, pretty, dont_print_vb); + + if (!len && n_baseclasses == 1) + fprintf_filtered (stream, "<No data fields>"); + else + { + extern int inspect_it; + int fields_seen = 0; + + if (dont_print_statmem == 0) + { + /* If we're at top level, carve out a completely fresh + chunk of the obstack and use that until this particular + invocation returns. */ + tmp_obstack = dont_print_statmem_obstack; + obstack_finish (&dont_print_statmem_obstack); + } + + for (i = n_baseclasses; i < len; i++) + { + /* If requested, skip printing of static fields. */ + if (!pascal_static_field_print && TYPE_FIELD_STATIC (type, i)) + continue; + if (fields_seen) + fprintf_filtered (stream, ", "); + else if (n_baseclasses > 0) + { + if (pretty) + { + fprintf_filtered (stream, "\n"); + print_spaces_filtered (2 + 2 * recurse, stream); + fputs_filtered ("members of ", stream); + fputs_filtered (type_name_no_tag (type), stream); + fputs_filtered (": ", stream); + } + } + fields_seen = 1; + + if (pretty) + { + fprintf_filtered (stream, "\n"); + print_spaces_filtered (2 + 2 * recurse, stream); + } + else + { + wrap_here (n_spaces (2 + 2 * recurse)); + } + if (inspect_it) + { + if (TYPE_CODE (TYPE_FIELD_TYPE (type, i)) == TYPE_CODE_PTR) + fputs_filtered ("\"( ptr \"", stream); + else + fputs_filtered ("\"( nodef \"", stream); + if (TYPE_FIELD_STATIC (type, i)) + fputs_filtered ("static ", stream); + fprintf_symbol_filtered (stream, TYPE_FIELD_NAME (type, i), + language_cplus, + DMGL_PARAMS | DMGL_ANSI); + fputs_filtered ("\" \"", stream); + fprintf_symbol_filtered (stream, TYPE_FIELD_NAME (type, i), + language_cplus, + DMGL_PARAMS | DMGL_ANSI); + fputs_filtered ("\") \"", stream); + } + else + { + annotate_field_begin (TYPE_FIELD_TYPE (type, i)); + + if (TYPE_FIELD_STATIC (type, i)) + fputs_filtered ("static ", stream); + fprintf_symbol_filtered (stream, TYPE_FIELD_NAME (type, i), + language_cplus, + DMGL_PARAMS | DMGL_ANSI); + annotate_field_name_end (); + fputs_filtered (" = ", stream); + annotate_field_value (); + } + + if (!TYPE_FIELD_STATIC (type, i) && TYPE_FIELD_PACKED (type, i)) + { + value_ptr v; + + /* Bitfields require special handling, especially due to byte + order problems. */ + if (TYPE_FIELD_IGNORE (type, i)) + { + fputs_filtered ("<optimized out or zero length>", stream); + } + else + { + v = value_from_longest (TYPE_FIELD_TYPE (type, i), + unpack_field_as_long (type, valaddr, i)); + + val_print (TYPE_FIELD_TYPE (type, i), VALUE_CONTENTS (v), 0, 0, + stream, format, 0, recurse + 1, pretty); + } + } + else + { + if (TYPE_FIELD_IGNORE (type, i)) + { + fputs_filtered ("<optimized out or zero length>", stream); + } + else if (TYPE_FIELD_STATIC (type, i)) + { + /* value_ptr v = value_static_field (type, i); v4.17 specific */ + value_ptr v; + v = value_from_longest (TYPE_FIELD_TYPE (type, i), + unpack_field_as_long (type, valaddr, i)); + + if (v == NULL) + fputs_filtered ("<optimized out>", stream); + else + pascal_object_print_static_field (TYPE_FIELD_TYPE (type, i), v, + stream, format, recurse + 1, + pretty); + } + else + { + /* val_print (TYPE_FIELD_TYPE (type, i), + valaddr + TYPE_FIELD_BITPOS (type, i) / 8, + address + TYPE_FIELD_BITPOS (type, i) / 8, 0, + stream, format, 0, recurse + 1, pretty); */ + val_print (TYPE_FIELD_TYPE (type, i), + valaddr, TYPE_FIELD_BITPOS (type, i) / 8, + address + TYPE_FIELD_BITPOS (type, i) / 8, + stream, format, 0, recurse + 1, pretty); + } + } + annotate_field_end (); + } + + if (dont_print_statmem == 0) + { + /* Free the space used to deal with the printing + of the members from top level. */ + obstack_free (&dont_print_statmem_obstack, last_dont_print); + dont_print_statmem_obstack = tmp_obstack; + } + + if (pretty) + { + fprintf_filtered (stream, "\n"); + print_spaces_filtered (2 * recurse, stream); + } + } + fprintf_filtered (stream, "}"); +} + +/* Special val_print routine to avoid printing multiple copies of virtual + baseclasses. */ + +void +pascal_object_print_value (type, valaddr, address, stream, format, recurse, pretty, + dont_print_vb) + struct type *type; + char *valaddr; + CORE_ADDR address; + struct ui_file *stream; + int format; + int recurse; + enum val_prettyprint pretty; + struct type **dont_print_vb; +{ + struct obstack tmp_obstack; + struct type **last_dont_print + = (struct type **) obstack_next_free (&dont_print_vb_obstack); + int i, n_baseclasses = TYPE_N_BASECLASSES (type); + + if (dont_print_vb == 0) + { + /* If we're at top level, carve out a completely fresh + chunk of the obstack and use that until this particular + invocation returns. */ + tmp_obstack = dont_print_vb_obstack; + /* Bump up the high-water mark. Now alpha is omega. */ + obstack_finish (&dont_print_vb_obstack); + } + + for (i = 0; i < n_baseclasses; i++) + { + int boffset; + struct type *baseclass = check_typedef (TYPE_BASECLASS (type, i)); + char *basename = TYPE_NAME (baseclass); + char *base_valaddr; + + if (BASETYPE_VIA_VIRTUAL (type, i)) + { + struct type **first_dont_print + = (struct type **) obstack_base (&dont_print_vb_obstack); + + int j = (struct type **) obstack_next_free (&dont_print_vb_obstack) + - first_dont_print; + + while (--j >= 0) + if (baseclass == first_dont_print[j]) + goto flush_it; + + obstack_ptr_grow (&dont_print_vb_obstack, baseclass); + } + + boffset = baseclass_offset (type, i, valaddr, address); + + if (pretty) + { + fprintf_filtered (stream, "\n"); + print_spaces_filtered (2 * recurse, stream); + } + fputs_filtered ("<", stream); + /* Not sure what the best notation is in the case where there is no + baseclass name. */ + + fputs_filtered (basename ? basename : "", stream); + fputs_filtered ("> = ", stream); + + /* The virtual base class pointer might have been clobbered by the + user program. Make sure that it still points to a valid memory + location. */ + + if (boffset != -1 && (boffset < 0 || boffset >= TYPE_LENGTH (type))) + { + base_valaddr = (char *) alloca (TYPE_LENGTH (baseclass)); + if (target_read_memory (address + boffset, base_valaddr, + TYPE_LENGTH (baseclass)) != 0) + boffset = -1; + } + else + base_valaddr = valaddr + boffset; + + if (boffset == -1) + fprintf_filtered (stream, "<invalid address>"); + else + pascal_object_print_value_fields (baseclass, base_valaddr, address + boffset, + stream, format, recurse, pretty, + (struct type **) obstack_base (&dont_print_vb_obstack), + 0); + fputs_filtered (", ", stream); + + flush_it: + ; + } + + if (dont_print_vb == 0) + { + /* Free the space used to deal with the printing + of this type from top level. */ + obstack_free (&dont_print_vb_obstack, last_dont_print); + /* Reset watermark so that we can continue protecting + ourselves from whatever we were protecting ourselves. */ + dont_print_vb_obstack = tmp_obstack; + } +} + +/* Print value of a static member. + To avoid infinite recursion when printing a class that contains + a static instance of the class, we keep the addresses of all printed + static member classes in an obstack and refuse to print them more + than once. + + VAL contains the value to print, TYPE, STREAM, RECURSE, and PRETTY + have the same meanings as in c_val_print. */ + +static void +pascal_object_print_static_field (type, val, stream, format, recurse, pretty) + struct type *type; + value_ptr val; + struct ui_file *stream; + int format; + int recurse; + enum val_prettyprint pretty; +{ + if (TYPE_CODE (type) == TYPE_CODE_STRUCT) + { + CORE_ADDR *first_dont_print; + int i; + + first_dont_print + = (CORE_ADDR *) obstack_base (&dont_print_statmem_obstack); + i = (CORE_ADDR *) obstack_next_free (&dont_print_statmem_obstack) + - first_dont_print; + + while (--i >= 0) + { + if (VALUE_ADDRESS (val) == first_dont_print[i]) + { + fputs_filtered ("<same as static member of an already seen type>", + stream); + return; + } + } + + obstack_grow (&dont_print_statmem_obstack, (char *) &VALUE_ADDRESS (val), + sizeof (CORE_ADDR)); + + CHECK_TYPEDEF (type); + pascal_object_print_value_fields (type, VALUE_CONTENTS (val), VALUE_ADDRESS (val), + stream, format, recurse, pretty, NULL, 1); + return; + } + val_print (type, VALUE_CONTENTS (val), 0, VALUE_ADDRESS (val), + stream, format, 0, recurse, pretty); +} + +void +pascal_object_print_class_member (valaddr, domain, stream, prefix) + char *valaddr; + struct type *domain; + struct ui_file *stream; + char *prefix; +{ + + /* VAL is a byte offset into the structure type DOMAIN. + Find the name of the field for that offset and + print it. */ + int extra = 0; + int bits = 0; + register unsigned int i; + unsigned len = TYPE_NFIELDS (domain); + /* @@ Make VAL into bit offset */ + LONGEST val = unpack_long (builtin_type_int, valaddr) << 3; + for (i = TYPE_N_BASECLASSES (domain); i < len; i++) + { + int bitpos = TYPE_FIELD_BITPOS (domain, i); + QUIT; + if (val == bitpos) + break; + if (val < bitpos && i != 0) + { + /* Somehow pointing into a field. */ + i -= 1; + extra = (val - TYPE_FIELD_BITPOS (domain, i)); + if (extra & 0x7) + bits = 1; + else + extra >>= 3; + break; + } + } + if (i < len) + { + char *name; + fprintf_filtered (stream, prefix); + name = type_name_no_tag (domain); + if (name) + fputs_filtered (name, stream); + else + pascal_type_print_base (domain, stream, 0, 0); + fprintf_filtered (stream, "::"); + fputs_filtered (TYPE_FIELD_NAME (domain, i), stream); + if (extra) + fprintf_filtered (stream, " + %d bytes", extra); + if (bits) + fprintf_filtered (stream, " (offset in bits)"); + } + else + fprintf_filtered (stream, "%ld", (long int) (val >> 3)); +} + + +void +_initialize_pascal_valprint () +{ + add_show_from_set + (add_set_cmd ("pascal_static-members", class_support, var_boolean, + (char *) &pascal_static_field_print, + "Set printing of pascal static members.", + &setprintlist), + &showprintlist); + /* Turn on printing of static fields. */ + pascal_static_field_print = 1; + +} |