A ton of changes to improve C++ debugging. See ChangeLog.

This commit is contained in:
Per Bothner 1992-09-04 07:37:18 +00:00
parent d73812a1d6
commit 35fcebce93
16 changed files with 619 additions and 182 deletions

View File

@ -1,3 +1,86 @@
Fri Sep 4 00:34:30 1992 Per Bothner (bothner@rtl.cygnus.com)
A bunch of changes mostly to improve debugging of C++ programs.
Specifically, nested types are supported, and the calling
of inferiors methods is improved.
* expression.h, c-exp.y: STRUCTOP_PTR and STRUCTOP_STRUCT
expression types now take an extra parameter that is used
for an (optional) type qualifier, as in: EXP.TYPE::NAME.
If there is no qualifier (as in EXP.NAME), the TYPE is NULL.
(Before, there was a cute but not-quote-valid re-write to
EXP.*(&TYPE::NAME .)
* parse.c (length_of_subexp, prefixify_subexp), expprint.c
(print_subexp), eval.c (evaluate_subexp): Handle the extra
operand of STRUCTOP_STRUCT and STRUCTOP_PTR.
* value.h: New macros METHOD_PTR_IS_VIRTUAL,
METHOD_PTR_FROM_VOFFSET, METHOD_PTR_TO_VOFFSET to partially
hide the implementation details of pointer-to-method objects.
How to tell if the pointer points to a virtual method is
still very dependent on the particular compiler, but this
should make it easier to find the places to change.
* eval.c (evaluate_subexp [case OP_FUNCALL]), valprint.c
(val_print [case TYPE_CODE_PTR]): Use the new METHOD_PTR_*
macros, instead of a hard-wired-in code that incorrectly
assumed a no-longerused representation of pointer-to-method
values. And otherwise fix the relevant bit-rotted code.
* valprint.c (type_print_base [case TYPE_CODE_STRUCT]):
If there are both fields and methods, put a space between.
* gdbtypes.h: New macro TYPE_FIELD_NESTED.
* symtab.C, syntab.h: New function find_nested_type()
searches a class recursively for a nested type.
* c-exp.y: Support nested type syntax: TYPE1::TYPE2.
This required some nasty interactions between the lexer
and the parser (surprise, surprise), using the current_type
global variable (see comment above its declaration),
and the new function find_nested_type().
* expprint.c (print_subexp), valprint.c (val_print_fields,
type_print_base [case TYPE_CODE_STRUCT]): Support nested types.
* stabsread.c (read_struct_type): Recognize types fields
nested in classes.
* gdbtypes.c, symtab.h: New functions check_struct,
check_union, and check_enum (factored out from lookup_struct,
lookup_union, lookup_enum).
* c-exp.y: Support 'enum Foo::Bar' syntax as just the same
as 'Foo::Bar' followed by a call to check_enum. Similarly
for struct and union.
* stabsread.c (read_struct_type): Fix bug in handling of
GNU C++ anonymous type (indicated by CPLUS_MARKER followed
by '_'). (It used to prematurely exit the loop reading in
the fields, so it would think it should start reading
methods while still in the fields. This could crash gdb
given a gcc that can emit nested type information.)
* valops.c (search_struct_method): Pass 'this' value by
reference instead of by value. This provides a more
consistent interface through a recursive search where the
"bottom" functions may need to adjust offsets (due to multiple
inheritance).
* valops.c, value.h, values.c: Pass extra parameters to
value_fn_field and value_virtual_fn_field so we can
correctly adjust offset for multiple inheritance.
* eval.c (evaluate_subexp [case OP_FUNCALL]): Simplify
virtual function calls by using value_virtual_fn_field().
* values.c: New function baseclass_offset, derived from
baseclass_addr (which perhaps can be made obsolete?).
It returns an offset rather than an address. This is a
cleaner interface since it doesn't mess around allocating
new values.
* valops.c (search_struct_method): Use baseclass_offset
rather than baseclass_addr.
* symfile.h: Declaration of set_demangling_style() moved
here from demangle.h (which is now in ../include).
* i386-xdep.c: Update comment.
* utils.c (strcmp_iw): Add a hack to allow "FOO(ARGS)" to
match "FOO". This allows 'break Foo' to work when Foo is
a mangled C++ function. (See comment before function.)
Thu Sep 3 09:17:05 1992 Stu Grossman (grossman at cygnus.com)
* a68v-xdep.c (store_inferior_registers): Define as type void.

View File

@ -42,6 +42,14 @@ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. */
#include "symfile.h"
#include "objfiles.h"
/* If current_type is non-NULL, it is a signal to the lexer that we have
just parsed: 'TYPE ::' and so if an identifier is seen, the lexer must
search for it in TYPE. This lex-time search is needed to parse
C++ nested types, as in: 'TYPE :: NESTED_TYPE', since this must
parse as a type, not a (non-type) identifier. */
static struct type *current_type = NULL;
/* These MUST be included in any grammar file!!!! Please choose unique names!
Note that this are a combined list of variables that can be produced
by any one of bison, byacc, or yacc. */
@ -120,7 +128,7 @@ parse_number PARAMS ((char *, int, int, YYSTYPE *));
%}
%type <voidval> exp exp1 type_exp start variable qualified_name
%type <tval> type typebase
%type <tval> type typebase typebase_coloncolon qualified_type
%type <tvec> nonempty_typelist
/* %type <bval> block */
@ -144,6 +152,7 @@ parse_number PARAMS ((char *, int, int, YYSTYPE *));
%token <sval> STRING
%token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
%token <tsym> TYPENAME
%token <tval> NESTED_TYPE
%type <sval> name
%type <ssym> name_not_typename
%type <tsym> typename
@ -265,16 +274,16 @@ exp : SIZEOF exp %prec UNARY
exp : exp ARROW name
{ write_exp_elt_opcode (STRUCTOP_PTR);
write_exp_elt_type (NULL);
write_exp_string ($3);
write_exp_elt_opcode (STRUCTOP_PTR); }
;
exp : exp ARROW qualified_name
{ /* exp->type::name becomes exp->*(&type::name) */
/* Note: this doesn't work if name is a
static member! FIXME */
write_exp_elt_opcode (UNOP_ADDR);
write_exp_elt_opcode (STRUCTOP_MPTR); }
exp : exp ARROW typebase_coloncolon name
{ write_exp_elt_opcode (STRUCTOP_PTR);
write_exp_elt_type ($3);
write_exp_string ($4);
write_exp_elt_opcode (STRUCTOP_PTR); }
;
exp : exp ARROW '*' exp
{ write_exp_elt_opcode (STRUCTOP_MPTR); }
@ -282,16 +291,16 @@ exp : exp ARROW '*' exp
exp : exp '.' name
{ write_exp_elt_opcode (STRUCTOP_STRUCT);
write_exp_elt_type (NULL);
write_exp_string ($3);
write_exp_elt_opcode (STRUCTOP_STRUCT); }
;
exp : exp '.' qualified_name
{ /* exp.type::name becomes exp.*(&type::name) */
/* Note: this doesn't work if name is a
static member! FIXME */
write_exp_elt_opcode (UNOP_ADDR);
write_exp_elt_opcode (STRUCTOP_MEMBER); }
exp : exp '.' typebase_coloncolon name
{ write_exp_elt_opcode (STRUCTOP_STRUCT);
write_exp_elt_type ($3);
write_exp_string ($4);
write_exp_elt_opcode (STRUCTOP_STRUCT); }
;
exp : exp '.' '*' exp
@ -576,7 +585,9 @@ variable: block COLONCOLON name
write_exp_elt_opcode (OP_VAR_VALUE); }
;
qualified_name: typebase COLONCOLON name
typebase_coloncolon : typebase COLONCOLON { current_type = $1; $$ = $1; }
qualified_name: typebase_coloncolon name
{
struct type *type = $1;
if (TYPE_CODE (type) != TYPE_CODE_STRUCT
@ -586,10 +597,11 @@ qualified_name: typebase COLONCOLON name
write_exp_elt_opcode (OP_SCOPE);
write_exp_elt_type (type);
write_exp_string ($3);
write_exp_string ($2);
write_exp_elt_opcode (OP_SCOPE);
current_type = NULL;
}
| typebase COLONCOLON '~' name
| typebase_coloncolon '~' name
{
struct type *type = $1;
struct stoken tmp_token;
@ -598,19 +610,20 @@ qualified_name: typebase COLONCOLON name
error ("`%s' is not defined as an aggregate type.",
TYPE_NAME (type));
if (strcmp (type_name_no_tag (type), $4.ptr))
if (strcmp (type_name_no_tag (type), $3.ptr))
error ("invalid destructor `%s::~%s'",
type_name_no_tag (type), $4.ptr);
type_name_no_tag (type), $3.ptr);
tmp_token.ptr = (char*) alloca ($4.length + 2);
tmp_token.length = $4.length + 1;
tmp_token.ptr = (char*) alloca ($3.length + 2);
tmp_token.length = $3.length + 1;
tmp_token.ptr[0] = '~';
memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
memcpy (tmp_token.ptr+1, $3.ptr, $3.length);
tmp_token.ptr[tmp_token.length] = 0;
write_exp_elt_opcode (OP_SCOPE);
write_exp_elt_type (type);
write_exp_string (tmp_token);
write_exp_elt_opcode (OP_SCOPE);
current_type = NULL;
}
;
@ -822,9 +835,15 @@ func_mod: '(' ')'
{ free ((PTR)$2); $$ = 0; }
;
qualified_type: typebase_coloncolon NESTED_TYPE
{ $$ = $2; current_type = NULL; }
;
type : ptype
| typebase COLONCOLON '*'
{ $$ = lookup_member_type (builtin_type_int, $1); }
| qualified_type
| typebase_coloncolon '*'
{ $$ = lookup_member_type (builtin_type_int, $1);
current_type = NULL; }
| type '(' typebase COLONCOLON '*' ')'
{ $$ = lookup_member_type ($1, $3); }
| type '(' typebase COLONCOLON '*' ')' '(' ')'
@ -876,6 +895,10 @@ typebase
| ENUM name
{ $$ = lookup_enum (copy_name ($2),
expression_context_block); }
| STRUCT qualified_type { $$ = check_struct ($2); }
| CLASS qualified_type { $$ = check_struct ($2); }
| UNION qualified_type { $$ = check_union ($2); }
| ENUM qualified_type { $$ = check_enum ($2); }
| UNSIGNED typename
{ $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
| UNSIGNED
@ -1419,6 +1442,17 @@ yylex ()
return VARIABLE;
}
if (current_type)
{
struct type *t =
find_nested_type (current_type, copy_name (yylval.sval));
if (t)
{
yylval.tval = t;
return NESTED_TYPE;
}
}
/* 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

View File

@ -296,39 +296,34 @@ evaluate_subexp (expect_type, exp, pos, noside)
arg1 = evaluate_subexp (NULL_TYPE, exp, pos, noside);
fnptr = longest_to_int (value_as_long (arg1));
/* FIXME-tiemann: this is way obsolete. */
if (fnptr < 128)
if (METHOD_PTR_IS_VIRTUAL(fnptr))
{
int fnoffset = METHOD_PTR_TO_VOFFSET(fnptr);
struct type *basetype;
struct type *domain_type =
TYPE_DOMAIN_TYPE (TYPE_TARGET_TYPE (VALUE_TYPE (arg1)));
int i, j;
basetype = TYPE_TARGET_TYPE (VALUE_TYPE (arg2));
basetype = TYPE_VPTR_BASETYPE (basetype);
if (domain_type != basetype)
arg2 = value_cast(lookup_pointer_type (domain_type), arg2);
basetype = TYPE_VPTR_BASETYPE (domain_type);
for (i = TYPE_NFN_FIELDS (basetype) - 1; i >= 0; i--)
{
struct fn_field *f = TYPE_FN_FIELDLIST1 (basetype, i);
/* If one is virtual, then all are virtual. */
if (TYPE_FN_FIELD_VIRTUAL_P (f, 0))
for (j = TYPE_FN_FIELDLIST_LENGTH (basetype, i) - 1; j >= 0; --j)
if (TYPE_FN_FIELD_VOFFSET (f, j) == fnptr)
if (TYPE_FN_FIELD_VOFFSET (f, j) == fnoffset)
{
value vtbl;
value base = value_ind (arg2);
struct type *fntype = lookup_pointer_type (TYPE_FN_FIELD_TYPE (f, j));
if (TYPE_VPTR_FIELDNO (basetype) < 0)
fill_in_vptr_fieldno (basetype);
VALUE_TYPE (base) = basetype;
vtbl = value_field (base, TYPE_VPTR_FIELDNO (basetype));
VALUE_TYPE (vtbl) = lookup_pointer_type (fntype);
VALUE_TYPE (arg1) = builtin_type_int;
arg1 = value_subscript (vtbl, arg1);
VALUE_TYPE (arg1) = fntype;
value temp = value_ind (arg2);
arg1 = value_virtual_fn_field (&temp, f, j, domain_type, 0);
arg2 = value_addr (temp);
goto got_it;
}
}
if (i < 0)
error ("virtual function at index %d not found", fnptr);
error ("virtual function at index %d not found", fnoffset);
}
else
{
@ -347,8 +342,9 @@ evaluate_subexp (expect_type, exp, pos, noside)
nargs = longest_to_int (exp->elts[pc + 1].longconst) + 1;
/* First, evaluate the structure into arg2 */
pc2 = (*pos)++;
tem2 = strlen (&exp->elts[pc2 + 1].string);
*pos += 2 + (tem2 + sizeof (union exp_element)) / sizeof (union exp_element);
/* type = exp->elts[pc2 + 1].type; */
tem2 = strlen (&exp->elts[pc2 + 2].string);
*pos += 3 + (tem2 + sizeof (union exp_element)) / sizeof (union exp_element);
if (noside == EVAL_SKIP)
goto nosideret;
@ -381,9 +377,13 @@ evaluate_subexp (expect_type, exp, pos, noside)
int static_memfuncp;
value temp = arg2;
/* argvec[0] gets the method;
argvec[1] gets the 'this' pointer (unless static) (from arg2);
the remaining args go into the rest of argvec. */
argvec[1] = arg2;
argvec[0] =
value_struct_elt (&temp, argvec+1, &exp->elts[pc2 + 1].string,
value_struct_elt (&temp, argvec+1, &exp->elts[pc2 + 2].string,
&static_memfuncp,
op == STRUCTOP_STRUCT
? "structure" : "structure pointer");
@ -428,40 +428,50 @@ evaluate_subexp (expect_type, exp, pos, noside)
return call_function_by_hand (argvec[0], nargs, argvec + 1);
case STRUCTOP_STRUCT:
tem = strlen (&exp->elts[pc + 1].string);
(*pos) += 2 + ((tem + sizeof (union exp_element))
tem = strlen (&exp->elts[pc + 2].string);
(*pos) += 3 + ((tem + sizeof (union exp_element))
/ sizeof (union exp_element));
arg1 = evaluate_subexp (NULL_TYPE, exp, pos, noside);
if (TYPE_CODE (VALUE_TYPE (arg1)) == TYPE_CODE_PTR)
goto handle_structop_ptr;
type = exp->elts[pc + 1].type;
if (type)
arg1 = value_ind (value_cast (lookup_pointer_type (type),
value_addr (arg1)));
if (noside == EVAL_SKIP)
goto nosideret;
if (noside == EVAL_AVOID_SIDE_EFFECTS)
return value_zero (lookup_struct_elt_type (VALUE_TYPE (arg1),
&exp->elts[pc + 1].string,
1),
&exp->elts[pc + 2].string,
0),
lval_memory);
else
{
value temp = arg1;
return value_struct_elt (&temp, (value *)0, &exp->elts[pc + 1].string,
return value_struct_elt (&temp, (value *)0, &exp->elts[pc + 2].string,
(int *) 0, "structure");
}
case STRUCTOP_PTR:
tem = strlen (&exp->elts[pc + 1].string);
(*pos) += 2 + (tem + sizeof (union exp_element)) / sizeof (union exp_element);
tem = strlen (&exp->elts[pc + 2].string);
(*pos) += 3 + (tem + sizeof (union exp_element)) / sizeof (union exp_element);
arg1 = evaluate_subexp (NULL_TYPE, exp, pos, noside);
handle_structop_ptr:
type = exp->elts[pc + 1].type;
if (type)
arg1 = value_cast (lookup_pointer_type (type), arg1);
if (noside == EVAL_SKIP)
goto nosideret;
if (noside == EVAL_AVOID_SIDE_EFFECTS)
return value_zero (lookup_struct_elt_type (TYPE_TARGET_TYPE
(VALUE_TYPE (arg1)),
&exp->elts[pc + 1].string,
1),
&exp->elts[pc + 2].string,
0),
lval_memory);
else
{
value temp = arg1;
return value_struct_elt (&temp, (value *)0, &exp->elts[pc + 1].string,
return value_struct_elt (&temp, (value *)0, &exp->elts[pc + 2].string,
(int *) 0, "structure pointer");
}
@ -564,8 +574,18 @@ evaluate_subexp (expect_type, exp, pos, noside)
if (noside == EVAL_SKIP)
goto nosideret;
if (noside == EVAL_AVOID_SIDE_EFFECTS)
return value_zero (TYPE_TARGET_TYPE (VALUE_TYPE (arg1)),
VALUE_LVAL (arg1));
{
/* If the user attempts to subscript something that has no target
type (like a plain int variable for example), then report this
as an error. */
type = TYPE_TARGET_TYPE (VALUE_TYPE (arg1));
if (type)
return value_zero (type, VALUE_LVAL (arg1));
else
error ("cannot subscript something of type `%s'",
TYPE_NAME (VALUE_TYPE (arg1)));
}
if (binop_user_defined_p (op, arg1, arg2))
return value_x_binop (arg1, arg2, op, OP_NULL);
@ -1068,7 +1088,7 @@ parse_and_eval_type (p, length)
char *tmp = (char *)alloca (length + 4);
struct expression *expr;
tmp[0] = '(';
(void) memcpy (tmp+1, p, length);
memcpy (tmp+1, p, length);
tmp[length+1] = ')';
tmp[length+2] = '0';
tmp[length+3] = '\0';

View File

@ -74,12 +74,9 @@ print_subexp (exp, pos, stream, prec)
/* Common ops */
case OP_SCOPE:
myprec = PREC_PREFIX;
assoc = 0;
(*pos) += 2;
print_subexp (exp, pos, stream,
(enum precedence) ((int) myprec + assoc));
fputs_filtered (" :: ", stream);
type_print (exp->elts[pc + 1].type, "", stream, 0);
fputs_filtered ("::", stream);
nargs = strlen (&exp->elts[pc + 2].string);
(*pos) += 1 + (nargs + sizeof (union exp_element)) / sizeof (union exp_element);
@ -114,7 +111,7 @@ print_subexp (exp, pos, stream, prec)
case OP_REGISTER:
(*pos) += 2;
fprintf_filtered (stream, "$%s",
reg_names[longest_to_int (exp->elts[pc + 1].longconst));
reg_names[longest_to_int (exp->elts[pc + 1].longconst)]);
return;
case OP_INTERNALVAR:
@ -163,20 +160,30 @@ print_subexp (exp, pos, stream, prec)
return;
case STRUCTOP_STRUCT:
tem = strlen (&exp->elts[pc + 1].string);
(*pos) += 2 + (tem + sizeof (union exp_element)) / sizeof (union exp_element);
tem = strlen (&exp->elts[pc + 2].string);
(*pos) += 3 + (tem + sizeof (union exp_element)) / sizeof (union exp_element);
print_subexp (exp, pos, stream, PREC_SUFFIX);
fputs_filtered (".", stream);
fputs_filtered (&exp->elts[pc + 1].string, stream);
if (exp->elts[pc + 1].type)
{
type_print (exp->elts[pc + 1].type, "", stream, 0);
fputs_filtered ("::", stream);
}
fputs_filtered (&exp->elts[pc + 2].string, stream);
return;
/* Will not occur for Modula-2 */
case STRUCTOP_PTR:
tem = strlen (&exp->elts[pc + 1].string);
(*pos) += 2 + (tem + sizeof (union exp_element)) / sizeof (union exp_element);
tem = strlen (&exp->elts[pc + 2].string);
(*pos) += 3 + (tem + sizeof (union exp_element)) / sizeof (union exp_element);
print_subexp (exp, pos, stream, PREC_SUFFIX);
fputs_filtered ("->", stream);
fputs_filtered (&exp->elts[pc + 1].string, stream);
if (exp->elts[pc + 1].type)
{
type_print (exp->elts[pc + 1].type, "", stream, 0);
fputs_filtered ("::", stream);
}
fputs_filtered (&exp->elts[pc + 2].string, stream);
return;
case BINOP_SUBSCRIPT:

View File

@ -1,21 +1,24 @@
/* Definitions for expressions stored in reversed prefix form, for GDB.
Copyright (C) 1986, 1989 Free Software Foundation, Inc.
Copyright 1986, 1989, 1992 Free Software Foundation, Inc.
This file is part of GDB.
GDB is free software; you can redistribute it and/or modify
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 1, or (at your option)
any later version.
the Free Software Foundation; either version 2 of the License, or
(at your option) any later version.
GDB is distributed in the hope that it will be useful,
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 GDB; see the file COPYING. If not, write to
the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA. */
along with this program; if not, write to the Free Software
Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. */
#if !defined (EXPRESSION_H)
#define EXPRESSION_H 1
/* Definitions for saved C expressions. */
@ -34,6 +37,10 @@ the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA. */
enum exp_opcode
{
/* Used when it's necessary to pass an opcode which will be ignored,
or to catch uninitialized values. */
OP_NULL,
/* BINOP_... operate on two values computed by following subexpressions,
replacing them by one result value. They take no immediate arguments. */
BINOP_ADD, /* + */
@ -58,6 +65,7 @@ enum exp_opcode
BINOP_ASSIGN, /* = */
BINOP_COMMA, /* , */
BINOP_SUBSCRIPT, /* x[y] */
BINOP_MULTI_SUBSCRIPT, /* Modula-2 x[a,b,...] */
BINOP_EXP, /* Exponentiation */
/* C++. */
@ -73,7 +81,8 @@ enum exp_opcode
STRUCTOP_MPTR,
/* end of C++. */
BINOP_END,
/* For Modula-2 integer division DIV */
BINOP_INTDIV,
BINOP_ASSIGN_MODIFY, /* +=, -=, *=, and so on.
The following exp_element is another opcode,
@ -81,6 +90,14 @@ enum exp_opcode
Then comes another BINOP_ASSIGN_MODIFY,
making three exp_elements in total. */
/* Modula-2 standard (binary) procedures*/
BINOP_VAL,
BINOP_INCL,
BINOP_EXCL,
/* This must be the highest BINOP_ value, for expprint.c. */
BINOP_END,
/* Operates on three values computed by following subexpressions. */
TERNOP_COND, /* ?: */
@ -146,6 +163,22 @@ enum exp_opcode
UNOP_POSTDECREMENT, /* -- after an expression */
UNOP_SIZEOF, /* Unary sizeof (followed by expression) */
UNOP_PLUS, /* Unary plus */
UNOP_CAP, /* Modula-2 standard (unary) procedures */
UNOP_CHR,
UNOP_ORD,
UNOP_ABS,
UNOP_FLOAT,
UNOP_HIGH,
UNOP_MAX,
UNOP_MIN,
UNOP_ODD,
UNOP_TRUNC,
OP_BOOL, /* Modula-2 builtin BOOLEAN type */
OP_M2_STRING, /* Modula-2 string constants */
/* STRUCTOP_... operate on a value from a following subexpression
by extracting a structure component specified by a string
that appears in the following exp_elements (as many as needed).
@ -153,6 +186,11 @@ enum exp_opcode
They differ only in the error message given in case the value is
not suitable or the structure component specified is not found.
After the sub-expression and before the string is a (struct type*).
This is normally NULL, but is used for the TYPE in a C++ qualified
reference like EXP.TYPE::NAME. (EXP.TYPE1::TYPE2::NAME does
not work, unfortunately.)
The length of the string follows in the next exp_element,
(after the string), followed by another STRUCTOP_... code. */
STRUCTOP_STRUCT,
@ -168,6 +206,10 @@ enum exp_opcode
a string, which, of course, is variable length. */
OP_SCOPE,
/* OP_TYPE is for parsing types, and used with the "ptype" command
so we can look up types that are qualified by scope, either with
the GDB "::" operator, or the Modula-2 '.' operator. */
OP_TYPE
};
union exp_element
@ -183,18 +225,30 @@ union exp_element
struct expression
{
const struct language_defn *language_defn; /* language it was entered in */
int nelts;
union exp_element elts[1];
};
/* From expread.y. */
struct expression *parse_c_expression ();
struct expression *parse_c_1 ();
/* From parse.c */
extern struct expression *
parse_expression PARAMS ((char *));
extern struct expression *
parse_exp_1 PARAMS ((char **, struct block *, int));
/* The innermost context required by the stack and register variables
we've encountered so far. To use this, set it to NULL, then call
parse_c_<whatever>, then look at it. */
parse_<whatever>, then look at it. */
extern struct block *innermost_block;
/* From expprint.c. */
void print_expression ();
/* From expprint.c */
extern void
print_expression PARAMS ((struct expression *, FILE *));
extern char *
op_string PARAMS ((enum exp_opcode));
#endif /* !defined (EXPRESSION_H) */

View File

@ -513,6 +513,15 @@ lookup_signed_typename (name)
return lookup_typename (name, (struct block *) NULL, 0);
}
struct type *
check_struct (type)
struct type *type;
{
if (TYPE_CODE (type) != TYPE_CODE_STRUCT)
error ("This context has %s, not a struct or class.", TYPE_NAME (type));
return type;
}
/* Lookup a structure type named "struct NAME",
visible in lexical block BLOCK. */
@ -530,11 +539,16 @@ lookup_struct (name, block)
{
error ("No struct type named %s.", name);
}
if (TYPE_CODE (SYMBOL_TYPE (sym)) != TYPE_CODE_STRUCT)
{
error ("This context has class, union or enum %s, not a struct.", name);
}
return (SYMBOL_TYPE (sym));
return check_struct (SYMBOL_TYPE (sym));
}
struct type *
check_union (type)
struct type *type;
{
if (TYPE_CODE (type) != TYPE_CODE_UNION)
error ("This context has %s, not a union.", TYPE_NAME (type));
return type;
}
/* Lookup a union type named "union NAME",
@ -554,11 +568,16 @@ lookup_union (name, block)
{
error ("No union type named %s.", name);
}
if (TYPE_CODE (SYMBOL_TYPE (sym)) != TYPE_CODE_UNION)
{
error ("This context has class, struct or enum %s, not a union.", name);
}
return (SYMBOL_TYPE (sym));
return check_union (SYMBOL_TYPE (sym));
}
struct type *
check_enum (type)
struct type *type;
{
if (TYPE_CODE (type) != TYPE_CODE_ENUM)
error ("This context has %s, not an enum.", TYPE_NAME (type));
return type;
}
/* Lookup an enum type named "enum NAME",
@ -577,11 +596,7 @@ lookup_enum (name, block)
{
error ("No enum type named %s.", name);
}
if (TYPE_CODE (SYMBOL_TYPE (sym)) != TYPE_CODE_ENUM)
{
error ("This context has class, struct or union %s, not an enum.", name);
}
return (SYMBOL_TYPE (sym));
return check_enum (SYMBOL_TYPE (sym));
}
/* Lookup a template type named "template NAME<TYPE>",

View File

@ -435,6 +435,7 @@ allocate_cplus_struct_type PARAMS ((struct type *));
B_TST(TYPE_CPLUS_SPECIFIC(thistype)->virtual_field_bits, (n))
#define TYPE_FIELD_STATIC(thistype, n) ((thistype)->fields[n].bitpos == -1)
#define TYPE_FIELD_NESTED(thistype, n) ((thistype)->fields[n].bitpos == -2)
#define TYPE_FIELD_STATIC_PHYSNAME(thistype, n) ((char *)(thistype)->fields[n].bitsize)
#define TYPE_FN_FIELDLISTS(thistype) TYPE_CPLUS_SPECIFIC(thistype)->fn_fieldlists

View File

@ -44,7 +44,7 @@ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. */
extern struct ext_format ext_format_i387;
/* this table must line up with REGISTER_NAMES in m-i386.h */
/* this table must line up with REGISTER_NAMES in tm-i386v.h */
/* symbols like 'EAX' come from <sys/reg.h> */
static int regmap[] =
{

View File

@ -275,6 +275,9 @@ length_of_subexp (expr, endpos)
switch (i)
{
case STRUCTOP_STRUCT:
case STRUCTOP_PTR:
args = 1;
/* C++ */
case OP_SCOPE:
oplen = 4 + ((expr->elts[endpos - 2].longconst
@ -326,9 +329,6 @@ length_of_subexp (expr, endpos)
args = 1;
break;
case STRUCTOP_STRUCT:
case STRUCTOP_PTR:
args = 1;
case OP_M2_STRING:
case OP_STRING:
oplen = 3 + ((expr->elts[endpos - 2].longconst
@ -393,6 +393,9 @@ prefixify_subexp (inexpr, outexpr, inend, outbeg)
opcode = inexpr->elts[inend - 1].opcode;
switch (opcode)
{
case STRUCTOP_STRUCT:
case STRUCTOP_PTR:
args = 1;
/* C++ */
case OP_SCOPE:
oplen = 4 + ((inexpr->elts[inend - 2].longconst
@ -443,9 +446,6 @@ prefixify_subexp (inexpr, outexpr, inend, outbeg)
args=1;
break;
case STRUCTOP_STRUCT:
case STRUCTOP_PTR:
args = 1;
case OP_M2_STRING:
case OP_STRING:
oplen = 3 + ((inexpr->elts[inend - 2].longconst

View File

@ -1158,7 +1158,8 @@ read_type (pp, objfile)
case '#': /* Method (class & fn) type */
if ((*pp)[0] == '#')
{
/* We'll get the parameter types from the name. */
/* This "minimized" format bogus, because it doesn't yield
enough information. I've changed gcc to not emit it. --Per */
struct type *return_type;
*pp += 1;
@ -1417,8 +1418,10 @@ read_struct_type (pp, type, objfile)
p = *pp;
if (*p == CPLUS_MARKER)
{
if (*p == '_') /* GNU C++ anonymous type. */
;
/* Special GNU C++ name. */
if (*++p == 'v')
else if (*++p == 'v')
{
const char *prefix;
char *name = 0;
@ -1457,15 +1460,12 @@ read_struct_type (pp, type, objfile)
list->field.bitsize = 0;
list->visibility = 0; /* private */
non_public_fields++;
nfields++;
continue;
}
/* GNU C++ anonymous type. */
else if (*p == '_')
break;
else
complain (&invalid_cpp_abbrev_complaint, *pp);
nfields++;
continue;
}
while (*p != ':') p++;
@ -1508,21 +1508,26 @@ read_struct_type (pp, type, objfile)
if (**pp == ':')
{
p = ++(*pp);
#if 0
/* Possible future hook for nested types. */
if (**pp == '!')
{
list->field.bitpos = (long)-2; /* nested type */
{ /* C++ nested type -as in FOO::BAR */
list->field.bitpos = (long)(-2); /* nested type */
p = ++(*pp);
if (TYPE_NAME (list->field.type) == NULL && **pp == '\'')
{
for (p = ++(*pp); *p != '\''; ) p++;
TYPE_NAME (list->field.type) = savestring (*pp, p - *pp);
}
while (*p != ';') p++;
list->field.bitsize = 0;
*pp = p + 1;
}
else
#endif
{ /* Static class member. */
list->field.bitpos = (long)-1;
list->field.bitpos = (long)(-1);
while (*p != ';') p++;
list->field.bitsize = (long) savestring (*pp, p - *pp);
*pp = p + 1;
}
while (*p != ';') p++;
list->field.bitsize = (long) savestring (*pp, p - *pp);
*pp = p + 1;
nfields++;
continue;
}

View File

@ -186,7 +186,8 @@ lookup_symtab_1 (name)
got_psymtab:
if (ps -> readin)
error ("Internal: readin pst for `%s' found when no symtab found.", name);
error ("Internal: readin %s pst for `%s' found when no symtab found.",
ps -> filename, name);
s = PSYMTAB_TO_SYMTAB (ps);
@ -262,13 +263,56 @@ gdb_mangle_name (type, i, j)
struct fn_field *method = &f[j];
char *field_name = TYPE_FN_FIELDLIST_NAME (type, i);
char *physname = TYPE_FN_FIELD_PHYSNAME (f, j);
char *opname;
int is_constructor = strcmp (field_name, type_name_no_tag (type)) == 0;
char *newname = type_name_no_tag (type);
int is_constructor = strcmp(field_name, newname) == 0;
int is_destructor = is_constructor && physname[0] == '_'
&& physname[1] == CPLUS_MARKER && physname[2] == '_';
/* Need a new type prefix. */
char *const_prefix = method->is_const ? "C" : "";
char *volatile_prefix = method->is_volatile ? "V" : "";
char buf[20];
#ifndef GCC_MANGLE_BUG
int len = strlen (newname);
if (is_destructor)
{
mangled_name = (char*) xmalloc(strlen(physname)+1);
strcpy(mangled_name, physname);
return mangled_name;
}
sprintf (buf, "__%s%s%d", const_prefix, volatile_prefix, len);
mangled_name_len = ((is_constructor ? 0 : strlen (field_name))
+ strlen (buf) + len
+ strlen (physname)
+ 1);
/* Only needed for GNU-mangled names. ANSI-mangled names
work with the normal mechanisms. */
if (OPNAME_PREFIX_P (field_name))
{
char *opname = cplus_mangle_opname (field_name + 3, 0);
if (opname == NULL)
error ("No mangling for \"%s\"", field_name);
mangled_name_len += strlen (opname);
mangled_name = (char *)xmalloc (mangled_name_len);
strncpy (mangled_name, field_name, 3);
mangled_name[3] = '\0';
strcat (mangled_name, opname);
}
else
{
mangled_name = (char *)xmalloc (mangled_name_len);
if (is_constructor)
mangled_name[0] = '\0';
else
strcpy (mangled_name, field_name);
}
strcat (mangled_name, buf);
strcat (mangled_name, newname);
#else
char *opname;
if (is_constructor)
{
@ -310,8 +354,9 @@ gdb_mangle_name (type, i, j)
}
}
strcat (mangled_name, buf);
strcat (mangled_name, physname);
#endif
strcat (mangled_name, physname);
return (mangled_name);
}
@ -521,7 +566,8 @@ found:
ALL_MSYMBOLS (objfile, msymbol)
{
demangled = demangle_and_match (msymbol -> name, name, 0);
demangled = demangle_and_match (msymbol -> name, name,
DMGL_PARAMS | DMGL_ANSI);
if (demangled != NULL)
{
free (demangled);
@ -579,7 +625,7 @@ found_msym:
block = BLOCKVECTOR_BLOCK (bv, GLOBAL_BLOCK);
sym = lookup_block_symbol (block, name, namespace);
if (!sym)
error ("Internal: global symbol `%s' found in psymtab but not in symtab", name);
error ("Internal: global symbol `%s' found in %s psymtab but not in symtab", name, ps->filename);
if (symtab != NULL)
*symtab = s;
return sym;
@ -613,7 +659,7 @@ found_msym:
block = BLOCKVECTOR_BLOCK (bv, STATIC_BLOCK);
sym = lookup_block_symbol (block, name, namespace);
if (!sym)
error ("Internal: static symbol `%s' found in psymtab but not in symtab", name);
error ("Internal: static symbol `%s' found in %s psymtab but not in symtab", name, ps->filename);
if (symtab != NULL)
*symtab = s;
return sym;
@ -648,7 +694,7 @@ found_msym:
block = BLOCKVECTOR_BLOCK (bv, STATIC_BLOCK);
sym = lookup_demangled_block_symbol (block, name);
if (!sym)
error ("Internal: mangled static symbol `%s' found in psymtab but not in symtab", name);
error ("Internal: mangled static symbol `%s' found in %s psymtab but not in symtab", name, ps->filename);
if (symtab != NULL)
*symtab = s;
return sym;
@ -680,7 +726,8 @@ lookup_demangled_block_symbol (block, name)
sym = BLOCK_SYM (block, bot);
if (SYMBOL_NAMESPACE (sym) == VAR_NAMESPACE)
{
demangled = demangle_and_match (SYMBOL_NAME (sym), name, 0);
demangled = demangle_and_match (SYMBOL_NAME (sym), name,
DMGL_PARAMS | DMGL_ANSI);
if (demangled != NULL)
{
free (demangled);
@ -712,7 +759,8 @@ lookup_demangled_partial_symbol (pst, name)
{
if (SYMBOL_NAMESPACE (psym) == VAR_NAMESPACE)
{
demangled = demangle_and_match (SYMBOL_NAME (psym), name, 0);
demangled = demangle_and_match (SYMBOL_NAME (psym), name,
DMGL_PARAMS | DMGL_ANSI);
if (demangled != NULL)
{
free (demangled);
@ -1221,6 +1269,31 @@ find_pc_line_pc_range (pc, startptr, endptr)
return sal.symtab != 0;
}
struct type *
find_nested_type (type, name)
struct type *type;
char *name;
{
int i;
for (i = TYPE_NFIELDS (type) - 1; i >= TYPE_N_BASECLASSES (type); i--)
{
char *t_field_name = TYPE_FIELD_NAME (type, i);
if (t_field_name && !strcmp (t_field_name, name))
if (TYPE_FIELD_NESTED (type, i))
{
return TYPE_FIELD_TYPE (type, i);
}
}
for (i = TYPE_N_BASECLASSES (type) - 1; i >= 0; i--)
{
struct type * t = find_nested_type (TYPE_BASECLASS (type, i), name);
if (t)
return t;
}
return NULL;
}
/* If P is of the form "operator[ \t]+..." where `...' is
some legitimate operator text, return a pointer to the
beginning of the substring of the operator text.

View File

@ -562,6 +562,15 @@ lookup_union PARAMS ((char *, struct block *));
extern struct type *
lookup_enum PARAMS ((char *, struct block *));
extern struct type *
check_struct PARAMS ((struct type *));
extern struct type *
check_union PARAMS ((struct type *));
extern struct type *
check_enum PARAMS ((struct type *));
extern struct symbol *
block_function PARAMS ((struct block *));
@ -668,6 +677,22 @@ decode_line_1 PARAMS ((char **, int, struct symtab *, int));
/* Symmisc.c */
#if MAINTENANCE_CMDS
void
maintenance_print_symbols PARAMS ((char *, int));
void
maintenance_print_psymbols PARAMS ((char *, int));
void
maintenance_print_msymbols PARAMS ((char *, int));
void
maintenance_print_objfiles PARAMS ((char *, int));
#endif
extern void
free_symtab PARAMS ((struct symtab *));
@ -707,6 +732,9 @@ clear_symtab_users_once PARAMS ((void));
extern struct partial_symtab *
find_main_psymtab PARAMS ((void));
extern struct type *
find_nested_type PARAMS ((struct type *, char*));
/* blockframe.c */
extern struct blockvector *

View File

@ -43,7 +43,7 @@ static value
search_struct_field PARAMS ((char *, value, int, struct type *, int));
static value
search_struct_method PARAMS ((char *, value, value *, int, int *,
search_struct_method PARAMS ((char *, value *, value *, int, int *,
struct type *));
static int
@ -1038,6 +1038,7 @@ search_struct_field (name, arg1, offset, type, looking_for_baseclass)
if (BASETYPE_VIA_VIRTUAL (type, i))
{
value v2;
/* Fix to use baseclass_offset instead. FIXME */
baseclass_addr (type, i, VALUE_CONTENTS (arg1) + offset,
&v2, (int *)NULL);
if (v2 == 0)
@ -1065,9 +1066,9 @@ search_struct_field (name, arg1, offset, type, looking_for_baseclass)
If found, return value, else return NULL. */
static value
search_struct_method (name, arg1, args, offset, static_memfuncp, type)
search_struct_method (name, arg1p, args, offset, static_memfuncp, type)
char *name;
register value arg1, *args;
register value *arg1p, *args;
int offset, *static_memfuncp;
register struct type *type;
{
@ -1092,10 +1093,10 @@ search_struct_method (name, arg1, args, offset, static_memfuncp, type)
TYPE_FN_FIELD_ARGS (f, j), args))
{
if (TYPE_FN_FIELD_VIRTUAL_P (f, j))
return (value)value_virtual_fn_field (arg1, f, j, type);
return (value)value_virtual_fn_field (arg1p, f, j, type, offset);
if (TYPE_FN_FIELD_STATIC_P (f, j) && static_memfuncp)
*static_memfuncp = 1;
return (value)value_fn_field (f, j);
return (value)value_fn_field (arg1p, f, j, type, offset);
}
j--;
}
@ -1104,25 +1105,27 @@ search_struct_method (name, arg1, args, offset, static_memfuncp, type)
for (i = TYPE_N_BASECLASSES (type) - 1; i >= 0; i--)
{
value v, v2;
value v;
int base_offset;
if (BASETYPE_VIA_VIRTUAL (type, i))
{
baseclass_addr (type, i, VALUE_CONTENTS (arg1) + offset,
&v2, (int *)NULL);
if (v2 == 0)
base_offset =
baseclass_offset (type, i, *arg1p, offset);
if (base_offset == -1)
error ("virtual baseclass botch");
base_offset = 0;
}
else
{
v2 = arg1;
base_offset = TYPE_BASECLASS_BITPOS (type, i) / 8;
}
v = search_struct_method (name, v2, args, base_offset,
v = search_struct_method (name, arg1p, args, base_offset + offset,
static_memfuncp, TYPE_BASECLASS (type, i));
if (v) return v;
if (v)
{
/* *arg1p = arg1_tmp;*/
return v;
}
}
return NULL;
}
@ -1193,7 +1196,7 @@ value_struct_elt (argp, args, name, static_memfuncp, err)
if (destructor_name_p (name, t))
error ("Cannot get value of destructor");
v = search_struct_method (name, *argp, args, 0, static_memfuncp, t);
v = search_struct_method (name, argp, args, 0, static_memfuncp, t);
if (v == 0)
{
@ -1210,8 +1213,9 @@ value_struct_elt (argp, args, name, static_memfuncp, err)
if (!args[1])
{
/* destructors are a special case. */
return (value)value_fn_field (TYPE_FN_FIELDLIST1 (t, 0),
TYPE_FN_FIELDLIST_LENGTH (t, 0));
return (value)value_fn_field (NULL, TYPE_FN_FIELDLIST1 (t, 0),
TYPE_FN_FIELDLIST_LENGTH (t, 0),
0, 0);
}
else
{
@ -1219,7 +1223,7 @@ value_struct_elt (argp, args, name, static_memfuncp, err)
}
}
else
v = search_struct_method (name, *argp, args, 0, static_memfuncp, t);
v = search_struct_method (name, argp, args, 0, static_memfuncp, t);
if (v == 0)
{
@ -1414,23 +1418,29 @@ value_struct_elt_for_reference (domain, offset, curtype, name, intype)
(lookup_reference_type
(lookup_member_type (TYPE_FN_FIELD_TYPE (f, j),
domain)),
(LONGEST) TYPE_FN_FIELD_VOFFSET (f, j));
METHOD_PTR_FROM_VOFFSET((LONGEST) TYPE_FN_FIELD_VOFFSET (f, j)));
}
else
{
struct symbol *s = lookup_symbol (TYPE_FN_FIELD_PHYSNAME (f, j),
0, VAR_NAMESPACE, 0, NULL);
v = read_var_value (s, 0);
#if 0
VALUE_TYPE (v) = lookup_reference_type
(lookup_member_type (TYPE_FN_FIELD_TYPE (f, j),
domain));
#endif
return v;
if (s == NULL)
{
v = 0;
}
else
{
v = read_var_value (s, 0);
#if 0
VALUE_TYPE (v) = lookup_reference_type
(lookup_member_type (TYPE_FN_FIELD_TYPE (f, j),
domain));
#endif
}
return v;
}
}
}
for (i = TYPE_N_BASECLASSES (t) - 1; i >= 0; i--)
{
value v;

View File

@ -510,7 +510,7 @@ val_print_fields (type, valaddr, stream, format, recurse, pretty, dont_print)
for (i = n_baseclasses; i < len; i++)
{
/* Check if static field */
if (TYPE_FIELD_STATIC (type, i))
if (TYPE_FIELD_STATIC (type, i) || TYPE_FIELD_NESTED (type, i))
continue;
if (fields_seen)
fprintf_filtered (stream, ", ");
@ -628,6 +628,7 @@ cplus_val_print (type, valaddr, stream, format, recurse, pretty, dont_print)
obstack_ptr_grow (&dont_print_obstack, TYPE_BASECLASS (type, i));
}
/* Fix to use baseclass_offset instead. FIXME */
baddr = baseclass_addr (type, i, valaddr, 0, &err);
if (err == 0 && baddr == 0)
error ("could not find virtual baseclass `%s'\n",
@ -867,8 +868,9 @@ val_print (type, valaddr, address, stream, format, deref_ref, recurse, pretty)
addr = unpack_pointer (lookup_pointer_type (builtin_type_void),
valaddr);
if (addr < 128) /* FIXME! What is this 128? */
if (METHOD_PTR_IS_VIRTUAL(addr))
{
int offset = METHOD_PTR_TO_VOFFSET(addr);
len = TYPE_NFN_FIELDS (domain);
for (i = 0; i < len; i++)
{
@ -878,9 +880,9 @@ val_print (type, valaddr, address, stream, format, deref_ref, recurse, pretty)
for (j = 0; j < len2; j++)
{
QUIT;
if (TYPE_FN_FIELD_VOFFSET (f, j) == addr)
if (TYPE_FN_FIELD_VOFFSET (f, j) == offset)
{
kind = "virtual";
kind = "virtual ";
goto common;
}
}
@ -1473,7 +1475,11 @@ type_print_derivation_info (stream, type)
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)");
fprintf_filtered (stream, "%s", name ? name : "(null)");
}
if (i > 0)
{
fputs_filtered (" ", stream);
}
}
@ -1841,10 +1847,14 @@ type_print_base (type, stream, show, level)
{
fprintf_filtered (stream, "static ");
}
if (TYPE_FIELD_NESTED (type, i))
{
fprintf_filtered (stream, "typedef ");
}
type_print_1 (TYPE_FIELD_TYPE (type, i),
TYPE_FIELD_NAME (type, i),
stream, show - 1, level + 4);
if (!TYPE_FIELD_STATIC (type, i)
if (!TYPE_FIELD_STATIC (type, i) && !TYPE_FIELD_NESTED (type, i)
&& TYPE_FIELD_PACKED (type, i))
{
/* It is a bitfield. This code does not attempt
@ -1858,8 +1868,13 @@ type_print_base (type, stream, show, level)
fprintf_filtered (stream, ";\n");
}
/* C++: print out the methods */
/* 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");
/* C++: print out the methods */
for (i = 0; i < len; i++)
{
struct fn_field *f = TYPE_FN_FIELDLIST1 (type, i);

View File

@ -52,7 +52,7 @@ struct value
{
/* Address in inferior or byte of registers structure. */
CORE_ADDR address;
/* Pointer to interrnal variable. */
/* Pointer to internal variable. */
struct internalvar *internalvar;
/* Number of register. Only used with
lval_reg_frame_relative. */
@ -62,7 +62,9 @@ struct value
int offset;
/* Only used for bitfields; number of bits contained in them. */
int bitsize;
/* Only used for bitfields; position of start of field. */
/* Only used for bitfields; position of start of field.
For BITS_BIG_ENDIAN=0 targets, it is the position of the LSB.
For BITS_BIG_ENDIAN=1 targets, it is the position of the MSB. */
int bitpos;
/* Frame value is relative to. In practice, this address is only
used if the value is stored in several registers in other than
@ -182,6 +184,12 @@ struct internalvar
value value;
};
/* Pointer to member function. Depends on compiler implementation. */
#define METHOD_PTR_IS_VIRTUAL(ADDR) ((ADDR) & 0x80000000)
#define METHOD_PTR_FROM_VOFFSET(OFFSET) (0x80000000 + (OFFSET))
#define METHOD_PTR_TO_VOFFSET(ADDR) (~0x80000000 & (ADDR))
#include "symtab.h"
#include "gdbtypes.h"
@ -212,7 +220,7 @@ unpack_double PARAMS ((struct type *type, char *valaddr, int *invp));
extern CORE_ADDR
unpack_pointer PARAMS ((struct type *type, char *valaddr));
extern long
extern LONGEST
unpack_field_as_long PARAMS ((struct type *type, char *valaddr,
int fieldno));
@ -298,6 +306,7 @@ value_struct_elt PARAMS ((value *argp, value *args, char *name,
extern value
value_struct_elt_for_reference PARAMS ((struct type *domain,
int offset,
struct type *curtype,
char *name,
struct type *intype));
@ -396,11 +405,12 @@ extern value
value_x_unop PARAMS ((value arg1, enum exp_opcode op));
extern value
value_fn_field PARAMS ((struct fn_field *f, int j));
value_fn_field PARAMS ((value *arg1p, struct fn_field *f, int j,
struct type* type, int offset));
extern value
value_virtual_fn_field PARAMS ((value arg1, struct fn_field *f, int j,
struct type *type));
value_virtual_fn_field PARAMS ((value *arg1p, struct fn_field *f, int j,
struct type *type, int offset));
extern int
binop_user_defined_p PARAMS ((enum exp_opcode op, value arg1, value arg2));
@ -414,7 +424,7 @@ typecmp PARAMS ((int staticp, struct type *t1[], value t2[]));
extern int
destructor_name_p PARAMS ((const char *name, const struct type *type));
#define value_free(val) free (val)
#define value_free(val) free ((PTR)val)
extern void
free_all_values PARAMS ((void));

View File

@ -903,12 +903,15 @@ value_field (arg1, fieldno)
J is an index into F which provides the desired method. */
value
value_fn_field (f, j)
value_fn_field (arg1p, f, j, type, offset)
value *arg1p;
struct fn_field *f;
int j;
struct type *type;
int offset;
{
register value v;
register struct type *type = TYPE_FN_FIELD_TYPE (f, j);
register struct type *ftype = TYPE_FN_FIELD_TYPE (f, j);
struct symbol *sym;
sym = lookup_symbol (TYPE_FN_FIELD_PHYSNAME (f, j),
@ -916,27 +919,40 @@ value_fn_field (f, j)
if (! sym) error ("Internal error: could not find physical method named %s",
TYPE_FN_FIELD_PHYSNAME (f, j));
v = allocate_value (type);
v = allocate_value (ftype);
VALUE_ADDRESS (v) = BLOCK_START (SYMBOL_BLOCK_VALUE (sym));
VALUE_TYPE (v) = type;
VALUE_TYPE (v) = ftype;
if (arg1p)
{
if (type != VALUE_TYPE (*arg1p))
*arg1p = value_ind (value_cast (lookup_pointer_type (type),
value_addr (*arg1p)));
/* Move the `this' pointer according to the offset. */
VALUE_OFFSET (*arg1p) += offset;
}
return v;
}
/* Return a virtual function as a value.
ARG1 is the object which provides the virtual function
table pointer. ARG1 is side-effected in calling this function.
table pointer. *ARG1P is side-effected in calling this function.
F is the list of member functions which contains the desired virtual
function.
J is an index into F which provides the desired virtual function.
TYPE is the type in which F is located. */
value
value_virtual_fn_field (arg1, f, j, type)
value arg1;
value_virtual_fn_field (arg1p, f, j, type, offset)
value *arg1p;
struct fn_field *f;
int j;
struct type *type;
int offset;
{
value arg1 = *arg1p;
/* First, get the virtual function table pointer. That comes
with a strange type, so cast it to type `pointer to long' (which
should serve just fine as a function type). Then, index into
@ -968,7 +984,9 @@ value_virtual_fn_field (arg1, f, j, type)
/* The virtual function table is now an array of structures
which have the form { int16 offset, delta; void *pfn; }. */
vtbl = value_ind (value_field (arg1, TYPE_VPTR_FIELDNO (context)));
vtbl = value_ind (value_primitive_field (arg1, 0,
TYPE_VPTR_FIELDNO (context),
TYPE_VPTR_BASETYPE (context)));
/* Index into the virtual function table. This is hard-coded because
looking up a field is not cheap, and it may be important to save
@ -977,7 +995,7 @@ value_virtual_fn_field (arg1, f, j, type)
entry = value_subscript (vtbl, vi);
/* Move the `this' pointer according to the virtual function table. */
VALUE_OFFSET (arg1) += value_as_long (value_field (entry, 0));
VALUE_OFFSET (arg1) += value_as_long (value_field (entry, 0)) + offset;
if (! VALUE_LAZY (arg1))
{
VALUE_LAZY (arg1) = 1;
@ -988,6 +1006,7 @@ value_virtual_fn_field (arg1, f, j, type)
/* Reinstantiate the function pointer with the correct type. */
VALUE_TYPE (vfn) = lookup_pointer_type (TYPE_FN_FIELD_TYPE (f, j));
*arg1p = arg1;
return vfn;
}
@ -1103,6 +1122,67 @@ value_from_vtable_info (arg, type)
return value_headof (arg, 0, type);
}
/* Compute the offset of the baseclass which is
the INDEXth baseclass of class TYPE, for a value ARG,
wih extra offset of OFFSET.
The result is the offste of the baseclass value relative
to (the address of)(ARG) + OFFSET.
-1 is returned on error. */
int
baseclass_offset (type, index, arg, offset)
struct type *type;
int index;
value arg;
int offset;
{
struct type *basetype = TYPE_BASECLASS (type, index);
if (BASETYPE_VIA_VIRTUAL (type, index))
{
/* Must hunt for the pointer to this virtual baseclass. */
register int i, len = TYPE_NFIELDS (type);
register int n_baseclasses = TYPE_N_BASECLASSES (type);
char *vbase_name, *type_name = type_name_no_tag (basetype);
vbase_name = (char *)alloca (strlen (type_name) + 8);
sprintf (vbase_name, "_vb%c%s", CPLUS_MARKER, type_name);
/* First look for the virtual baseclass pointer
in the fields. */
for (i = n_baseclasses; i < len; i++)
{
if (! strcmp (vbase_name, TYPE_FIELD_NAME (type, i)))
{
CORE_ADDR addr
= unpack_pointer (TYPE_FIELD_TYPE (type, i),
VALUE_CONTENTS (arg) + VALUE_OFFSET (arg)
+ offset
+ (TYPE_FIELD_BITPOS (type, i) / 8));
if (VALUE_LVAL (arg) != lval_memory)
return -1;
return addr -
(LONGEST) (VALUE_ADDRESS (arg) + VALUE_OFFSET (arg) + offset);
}
}
/* Not in the fields, so try looking through the baseclasses. */
for (i = index+1; i < n_baseclasses; i++)
{
int boffset =
baseclass_offset (type, i, arg, offset);
if (boffset)
return boffset;
}
/* Not found. */
return -1;
}
/* Baseclass is easily computed. */
return TYPE_BASECLASS_BITPOS (type, index) / 8;
}
/* Compute the address of the baseclass which is
the INDEXth baseclass of class TYPE. The TYPE base
of the object is at VALADDR.
@ -1112,6 +1192,8 @@ value_from_vtable_info (arg, type)
of the baseclasss, but the address which could not be read
successfully. */
/* FIXME Fix remaining uses of baseclass_addr to use baseclass_offset */
char *
baseclass_addr (type, index, valaddr, valuep, errp)
struct type *type;