/* YACC grammar for Modula-2 expressions, for GDB.
- Copyright (C) 1986, 1989, 1990, 1991 Free Software Foundation, Inc.
+ Copyright 1986, 1989, 1990, 1991, 1992, 1993, 1994, 1995, 1996, 1999,
+ 2000
+ Free Software Foundation, Inc.
Generated from expread.y (now c-exp.y) and contributed by the Department
of Computer Science at the State University of New York at Buffalo, 1991.
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., 675 Mass Ave, Cambridge, MA 02139, USA. */
+Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */
/* Parse a Modula-2 expression from text in a string,
and return the result as a struct expression pointer.
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. */
+ 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. */
%{
-#include <stdio.h>
-#include <string.h>
+
#include "defs.h"
-#include "param.h"
-#include "symtab.h"
-#include "frame.h"
+#include "gdb_string.h"
#include "expression.h"
#include "language.h"
+#include "value.h"
#include "parser-defs.h"
-
-/* These MUST be included in any grammar file!!!!
- Please choose unique names! */
+#include "m2-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 m2_maxdepth
#define yyparse m2_parse
#define yylex m2_lex
#define yyerror m2_error
#define yypgo m2_pgo
#define yyact m2_act
#define yyexca m2_exca
-
-void yyerror ();
-static int yylex ();
+#define yyerrflag m2_errflag
+#define yynerrs m2_nerrs
+#define yyps m2_ps
+#define yypv m2_pv
+#define yys m2_s
+#define yy_yys m2_yys
+#define yystate m2_state
+#define yytmp m2_tmp
+#define yyv m2_v
+#define yy_yyv m2_yyv
+#define yyval m2_val
+#define yylloc m2_lloc
+#define yyreds m2_reds /* With YYDEBUG defined */
+#define yytoks m2_toks /* With YYDEBUG defined */
+#define yylhs m2_yylhs
+#define yylen m2_yylen
+#define yydefred m2_yydefred
+#define yydgoto m2_yydgoto
+#define yysindex m2_yysindex
+#define yyrindex m2_yyrindex
+#define yygindex m2_yygindex
+#define yytable m2_yytable
+#define yycheck m2_yycheck
+
+#ifndef YYDEBUG
+#define YYDEBUG 1 /* Default to yydebug support */
+#endif
+
+#define YYFPRINTF parser_fprintf
+
+int yyparse (void);
+
+static int yylex (void);
+
+void yyerror (char *);
+
+#if 0
+static char *make_qualname (char *, char *);
+#endif
+
+static int parse_number (int);
/* The sign of the number being parsed. */
-int number_sign = 1;
+static int number_sign = 1;
/* The block that the module specified by the qualifer on an identifer is
contained in, */
-struct block *modblock=0;
-
-char *make_qualname();
-
-/* #define YYDEBUG 1 */
+#if 0
+static struct block *modblock=0;
+#endif
%}
%union
{
LONGEST lval;
- unsigned LONGEST ulval;
- double dval;
+ ULONGEST ulval;
+ DOUBLEST dval;
struct symbol *sym;
struct type *tval;
struct stoken sval;
%type <sym> fblock
%token <lval> INT HEX ERROR
-%token <ulval> UINT TRUE FALSE CHAR
+%token <ulval> UINT M2_TRUE M2_FALSE CHAR
%token <dval> FLOAT
/* Both NAME and TYPENAME tokens represent symbols in the input,
nonterminal "name", which matches either NAME or TYPENAME. */
%token <sval> STRING
-%token <sval> NAME BLOCKNAME IDENT CONST VARNAME
+%token <sval> NAME BLOCKNAME IDENT VARNAME
%token <sval> TYPENAME
-%token SIZE CAP ORD HIGH ABS MIN MAX FLOAT_FUNC VAL CHR ODD TRUNC
+%token SIZE CAP ORD HIGH ABS MIN_FUNC MAX_FUNC FLOAT_FUNC VAL CHR ODD TRUNC
%token INC DEC INCL EXCL
/* The GDB scope operator */
%token COLONCOLON
-%token <lval> LAST REGNAME
-
-%token <ivar> INTERNAL_VAR
+%token <voidval> INTERNAL_VAR
/* M2 tokens */
%left ','
%left ABOVE_COMMA
%nonassoc ASSIGN
%left '<' '>' LEQ GEQ '=' NOTEQUAL '#' IN
-%left OR
-%left AND '&'
+%left OROR
+%left LOGICAL_AND '&'
%left '@'
%left '+' '-'
%left '*' '/' DIV MOD
/* This is not an actual token ; it is used for precedence.
%right QID
*/
+
+\f
%%
start : exp
;
exp : not_exp exp %prec UNARY
- { write_exp_elt_opcode (UNOP_ZEROP); }
+ { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
;
not_exp : NOT
{ write_exp_elt_opcode (UNOP_HIGH); }
;
-exp : MIN '(' type ')'
+exp : MIN_FUNC '(' type ')'
{ write_exp_elt_opcode (UNOP_MIN);
write_exp_elt_type ($3);
write_exp_elt_opcode (UNOP_MIN); }
;
-exp : MAX '(' type ')'
+exp : MAX_FUNC '(' type ')'
{ write_exp_elt_opcode (UNOP_MAX);
write_exp_elt_type ($3);
write_exp_elt_opcode (UNOP_MIN); }
function types */
{ start_arglist(); }
non_empty_arglist ']' %prec DOT
- { write_exp_elt_opcode (BINOP_MULTI_SUBSCRIPT);
+ { write_exp_elt_opcode (MULTI_SUBSCRIPT);
write_exp_elt_longcst ((LONGEST) end_arglist());
- write_exp_elt_opcode (BINOP_MULTI_SUBSCRIPT); }
+ write_exp_elt_opcode (MULTI_SUBSCRIPT); }
;
exp : exp '('
{ write_exp_elt_opcode (BINOP_GTR); }
;
-exp : exp AND exp
- { write_exp_elt_opcode (BINOP_AND); }
+exp : exp LOGICAL_AND exp
+ { write_exp_elt_opcode (BINOP_LOGICAL_AND); }
;
-exp : exp '&' exp
- { write_exp_elt_opcode (BINOP_AND); }
- ;
-
-exp : exp OR exp
- { write_exp_elt_opcode (BINOP_OR); }
+exp : exp OROR exp
+ { write_exp_elt_opcode (BINOP_LOGICAL_OR); }
;
exp : exp ASSIGN exp
/* Constants */
-exp : TRUE
+exp : M2_TRUE
{ write_exp_elt_opcode (OP_BOOL);
write_exp_elt_longcst ((LONGEST) $1);
write_exp_elt_opcode (OP_BOOL); }
;
-exp : FALSE
+exp : M2_FALSE
{ write_exp_elt_opcode (OP_BOOL);
write_exp_elt_longcst ((LONGEST) $1);
write_exp_elt_opcode (OP_BOOL); }
exp : variable
;
-/* The GDB internal variable $$, et al. */
-exp : LAST
- { write_exp_elt_opcode (OP_LAST);
- write_exp_elt_longcst ((LONGEST) $1);
- write_exp_elt_opcode (OP_LAST); }
- ;
-
-exp : REGNAME
- { write_exp_elt_opcode (OP_REGISTER);
- write_exp_elt_longcst ((LONGEST) $1);
- write_exp_elt_opcode (OP_REGISTER); }
- ;
-
exp : SIZE '(' type ')' %prec UNARY
{ write_exp_elt_opcode (OP_LONG);
write_exp_elt_type (builtin_type_int);
/* Useful for assigning to PROCEDURE variables */
variable: fblock
{ write_exp_elt_opcode(OP_VAR_VALUE);
+ write_exp_elt_block (NULL);
write_exp_elt_sym ($1);
write_exp_elt_opcode (OP_VAR_VALUE); }
;
/* GDB internal ($foo) variable */
variable: INTERNAL_VAR
- { write_exp_elt_opcode (OP_INTERNALVAR);
- write_exp_elt_intern ($1);
- write_exp_elt_opcode (OP_INTERNALVAR); }
;
/* GDB scope operator */
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); }
;
NULL);
if (sym)
{
- switch (sym->class)
+ if (symbol_read_needs_frame (sym))
{
- case LOC_REGISTER:
- case LOC_ARG:
- case LOC_LOCAL:
if (innermost_block == 0 ||
- contained_in (block_found,
+ 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
{
- register int i;
+ struct minimal_symbol *msymbol;
register char *arg = copy_name ($1);
- for (i = 0; i < misc_function_count; i++)
- if (!strcmp (misc_function_vector[i].name, arg))
- break;
-
- if (i < misc_function_count)
+ msymbol =
+ lookup_minimal_symbol (arg, NULL, NULL);
+ if (msymbol != NULL)
{
- enum misc_function_type mft =
- (enum misc_function_type)
- misc_function_vector[i].type;
-
- write_exp_elt_opcode (OP_LONG);
- write_exp_elt_type (builtin_type_int);
- write_exp_elt_longcst ((LONGEST) misc_function_vector[i].address);
- write_exp_elt_opcode (OP_LONG);
- write_exp_elt_opcode (UNOP_MEMVAL);
- if (mft == mf_data || mft == mf_bss)
- write_exp_elt_type (builtin_type_int);
- else if (mft == mf_text)
- write_exp_elt_type (lookup_function_type (builtin_type_int));
- else
- write_exp_elt_type (builtin_type_char);
- write_exp_elt_opcode (UNOP_MEMVAL);
+ write_exp_msymbol
+ (msymbol,
+ lookup_function_type (builtin_type_int),
+ builtin_type_int);
}
- else if (symtab_list == 0
- && partial_symtab_list == 0)
+ else if (!have_full_symbols () && !have_partial_symbols ())
error ("No symbol table is loaded. Use the \"symbol-file\" command.");
else
error ("No symbol \"%s\" in current context.",
register int c,i,ischar=0;
register int base = input_radix;
register int len = olen;
- char *err_copy;
int unsigned_p = number_sign == 1 ? 1 : 0;
- extern double atof ();
-
if(p[len-1] == 'H')
{
base = 16;
int token;
} tokentab2[] =
{
- {"<>", NOTEQUAL },
- {":=", ASSIGN },
- {"<=", LEQ },
- {">=", GEQ },
- {"::", COLONCOLON },
+ { {'<', '>'}, NOTEQUAL },
+ { {':', '='}, ASSIGN },
+ { {'<', '='}, LEQ },
+ { {'>', '='}, GEQ },
+ { {':', ':'}, COLONCOLON },
};
static struct keyword keytab[] =
{
- {"OR" , OR },
+ {"OR" , OROR },
{"IN", IN },/* Note space after IN */
- {"AND", AND },
+ {"AND", LOGICAL_AND},
{"ABS", ABS },
{"CHR", CHR },
{"DEC", DEC },
{"NOT", NOT },
{"DIV", DIV },
{"INC", INC },
- {"MAX", MAX },
- {"MIN", MIN },
+ {"MAX", MAX_FUNC },
+ {"MIN", MIN_FUNC },
{"MOD", MOD },
{"ODD", ODD },
{"CAP", CAP },
retry:
+ prev_lexptr = lexptr;
+
tokstart = lexptr;
/* See if it is a special token of length 2 */
- for( i = 0 ; i < sizeof tokentab2 / sizeof tokentab2[0] ; i++)
- if(!strncmp(tokentab2[i].name, tokstart, 2))
+ for( i = 0 ; i < (int) (sizeof tokentab2 / sizeof tokentab2[0]) ; i++)
+ if(STREQN(tokentab2[i].name, tokstart, 2))
{
lexptr += 2;
return tokentab2[i].token;
{
char *err_copy = (char *) alloca (p - tokstart + 1);
- bcopy (tokstart, err_copy, p - tokstart);
+ memcpy (err_copy, tokstart, p - tokstart);
err_copy[p - tokstart] = 0;
error ("Invalid number \"%s\".", err_copy);
}
lexptr += namelen;
- /* Handle the tokens $digits; also $ (short for $0) and $$ (short for $$1)
- and $$digits (equivalent to $<-digits> if you could type that).
- Make token type LAST, and put the number (the digits) in yylval. */
-
- if (*tokstart == '$')
- {
- register int negate = 0;
- c = 1;
- /* Double dollar means negate the number and add -1 as well.
- Thus $$ alone means -1. */
- if (namelen >= 2 && tokstart[1] == '$')
- {
- negate = 1;
- c = 2;
- }
- if (c == namelen)
- {
- /* Just dollars (one or two) */
- yylval.lval = - negate;
- return LAST;
- }
- /* Is the rest of the token digits? */
- for (; c < namelen; c++)
- if (!(tokstart[c] >= '0' && tokstart[c] <= '9'))
- break;
- if (c == namelen)
- {
- yylval.lval = atoi (tokstart + 1 + negate);
- if (negate)
- yylval.lval = - yylval.lval;
- return LAST;
- }
- }
-
- /* Handle tokens that refer to machine registers:
- $ followed by a register name. */
-
- if (*tokstart == '$') {
- for (c = 0; c < NUM_REGS; c++)
- if (namelen - 1 == strlen (reg_names[c])
- && !strncmp (tokstart + 1, reg_names[c], namelen - 1))
- {
- yylval.lval = c;
- return REGNAME;
- }
- for (c = 0; c < num_std_regs; c++)
- if (namelen - 1 == strlen (std_regs[c].name)
- && !strncmp (tokstart + 1, std_regs[c].name, namelen - 1))
- {
- yylval.lval = std_regs[c].regnum;
- return REGNAME;
- }
- }
-
-
/* Lookup special keywords */
- for(i = 0 ; i < sizeof(keytab) / sizeof(keytab[0]) ; i++)
- if(namelen == strlen(keytab[i].keyw) && !strncmp(tokstart,keytab[i].keyw,namelen))
+ for(i = 0 ; i < (int) (sizeof(keytab) / sizeof(keytab[0])) ; i++)
+ if(namelen == strlen(keytab[i].keyw) && STREQN(tokstart,keytab[i].keyw,namelen))
return keytab[i].token;
yylval.sval.ptr = tokstart;
yylval.sval.length = namelen;
- /* Any other names starting in $ are debugger internal variables. */
-
if (*tokstart == '$')
{
- yylval.ivar = (struct internalvar *) lookup_internalvar (copy_name (yylval.sval) + 1);
+ write_dollar_variable (yylval.sval);
return INTERNAL_VAR;
}
-
/* Use token-type BLOCKNAME for symbols that happen to be defined as
functions. If this is not so, then ...
Use token-type TYPENAME for symbols that happen to be defined
if(sym)
{
- switch(sym->class)
+ switch(sym->aclass)
{
case LOC_STATIC:
case LOC_REGISTER:
case LOC_ARG:
case LOC_REF_ARG:
case LOC_REGPARM:
+ case LOC_REGPARM_ADDR:
case LOC_LOCAL:
case LOC_LOCAL_ARG:
+ case LOC_BASEREG:
+ case LOC_BASEREG_ARG:
case LOC_CONST:
case LOC_CONST_BYTES:
+ case LOC_OPTIMIZED_OUT:
return NAME;
case LOC_TYPEDEF:
error("internal: Undefined class in m2lex()");
case LOC_LABEL:
+ case LOC_UNRESOLVED:
error("internal: Unforseen case in m2lex()");
+
+ default:
+ error ("unhandled token in m2lex()");
+ break;
}
}
else
{
/* Built-in BOOLEAN type. This is sort of a hack. */
- if(!strncmp(tokstart,"TRUE",4))
+ if(STREQN(tokstart,"TRUE",4))
{
yylval.ulval = 1;
- return TRUE;
+ return M2_TRUE;
}
- else if(!strncmp(tokstart,"FALSE",5))
+ else if(STREQN(tokstart,"FALSE",5))
{
yylval.ulval = 0;
- return FALSE;
+ return M2_FALSE;
}
}
}
}
-char *
+#if 0 /* Unused */
+static char *
make_qualname(mod,ident)
char *mod, *ident;
{
- char *new = xmalloc(strlen(mod)+strlen(ident)+2);
+ char *new = malloc(strlen(mod)+strlen(ident)+2);
strcpy(new,mod);
strcat(new,".");
strcat(new,ident);
return new;
}
-
+#endif /* 0 */
void
-yyerror()
-{
- printf("Parsing: %s\n",lexptr);
- if (yychar < 256)
- error("Invalid syntax in expression near character '%c'.",yychar);
- else
- error("Invalid syntax in expression near a '%s'.",
- yytname[yychar-255]);
-}
-\f
-/* Table of operators and their precedences for printing expressions. */
-
-const static struct op_print m2_op_print_tab[] = {
- {"+", BINOP_ADD, PREC_ADD, 0},
- {"+", UNOP_PLUS, PREC_PREFIX, 0},
- {"-", BINOP_SUB, PREC_ADD, 0},
- {"-", UNOP_NEG, PREC_PREFIX, 0},
- {"*", BINOP_MUL, PREC_MUL, 0},
- {"/", BINOP_DIV, PREC_MUL, 0},
- {"DIV", BINOP_INTDIV, PREC_MUL, 0},
- {"MOD", BINOP_REM, PREC_MUL, 0},
- {":=", BINOP_ASSIGN, PREC_ASSIGN, 1},
- {"OR", BINOP_OR, PREC_OR, 0},
- {"AND", BINOP_AND, PREC_AND, 0},
- {"NOT", UNOP_ZEROP, PREC_PREFIX, 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},
- {"^", UNOP_IND, PREC_PREFIX, 0},
- {"@", BINOP_REPEAT, PREC_REPEAT, 0},
-};
-\f
-/* The built-in types of Modula-2. */
-
-struct type *builtin_type_m2_char;
-struct type *builtin_type_m2_int;
-struct type *builtin_type_m2_card;
-struct type *builtin_type_m2_real;
-struct type *builtin_type_m2_bool;
-
-struct type ** const (m2_builtin_types[]) =
+yyerror (msg)
+ char *msg;
{
- &builtin_type_m2_char,
- &builtin_type_m2_int,
- &builtin_type_m2_card,
- &builtin_type_m2_real,
- &builtin_type_m2_bool,
- 0
-};
-
-const struct language_defn m2_language_defn = {
- "modula-2",
- language_m2,
- m2_builtin_types,
- range_check_on,
- type_check_on,
- m2_parse, /* parser */
- m2_error, /* parser error function */
- &builtin_type_m2_int, /* longest signed integral type */
- &builtin_type_m2_card, /* longest unsigned integral type */
- &builtin_type_m2_real, /* longest floating point type */
- "0%XH", "0%", "XH", /* Hex format string, prefix, suffix */
- "%oB", "%", "oB", /* Octal format string, prefix, suffix */
- m2_op_print_tab, /* expression operators for printing */
- LANG_MAGIC
-};
+ if (prev_lexptr)
+ lexptr = prev_lexptr;
-/* Initialization for Modula-2 */
-
-void
-_initialize_m2_exp ()
-{
- /* FIXME: The code below assumes that the sizes of the basic data
- types are the same on the host and target machines!!! */
-
- /* Modula-2 "pervasive" types. NOTE: these can be redefined!!! */
- builtin_type_m2_int = init_type (TYPE_CODE_INT, sizeof(int), 0, "INTEGER");
- builtin_type_m2_card = init_type (TYPE_CODE_INT, sizeof(int), 1, "CARDINAL");
- builtin_type_m2_real = init_type (TYPE_CODE_FLT, sizeof(float), 0, "REAL");
- builtin_type_m2_char = init_type (TYPE_CODE_CHAR, sizeof(char), 1, "CHAR");
-
- builtin_type_m2_bool = init_type (TYPE_CODE_BOOL, sizeof(int), 1, "BOOLEAN");
- TYPE_NFIELDS(builtin_type_m2_bool) = 2;
- TYPE_FIELDS(builtin_type_m2_bool) =
- (struct field *) malloc (sizeof (struct field) * 2);
- TYPE_FIELD_BITPOS(builtin_type_m2_bool,0) = 0;
- TYPE_FIELD_NAME(builtin_type_m2_bool,0) = (char *)malloc(6);
- strcpy(TYPE_FIELD_NAME(builtin_type_m2_bool,0),"FALSE");
- TYPE_FIELD_BITPOS(builtin_type_m2_bool,1) = 1;
- TYPE_FIELD_NAME(builtin_type_m2_bool,1) = (char *)malloc(5);
- strcpy(TYPE_FIELD_NAME(builtin_type_m2_bool,1),"TRUE");
-
- add_language (&m2_language_defn);
+ error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr);
}