* config/obj-coffbfd.c (fill_section): Don't set NOLOAD bit for
[deliverable/binutils-gdb.git] / gdb / m2-exp.y
index ce81e63c99bb5d7297c30ca371ec01558a9d0679..8a7dbbacbf33c6c44ff77aec5a84c080dd3ae931 100644 (file)
@@ -26,21 +26,33 @@ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.  */
    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 "expression.h"
 #include "language.h"
+#include "value.h"
 #include "parser-defs.h"
+#include "m2-lang.h"
+
+/* 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. */
 
-/* These MUST be included in any grammar file!!!!
-   Please choose unique names! */
+#define        yymaxdepth m2_maxdepth
 #define        yyparse m2_parse
 #define        yylex   m2_lex
 #define        yyerror m2_error
@@ -57,22 +69,48 @@ Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.  */
 #define        yyexca  m2_exca
 #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 */
+
+#ifndef YYDEBUG
+#define        YYDEBUG 0               /* Default to no yydebug support */
+#endif
+
+int
+yyparse PARAMS ((void));
+
+static int
+yylex PARAMS ((void));
+
+void
+yyerror PARAMS ((char *));
 
-/* Forward decl's */
-void yyerror ();
-static int yylex ();
-int yyparse ();
+#if 0
+static char *
+make_qualname PARAMS ((char *, char *));
+#endif
+
+static int
+parse_number PARAMS ((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
 
 %}
 
@@ -104,7 +142,7 @@ char *make_qualname();
 %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,
@@ -117,10 +155,10 @@ char *make_qualname();
    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 */
@@ -135,8 +173,8 @@ char *make_qualname();
 %left ABOVE_COMMA
 %nonassoc ASSIGN
 %left '<' '>' LEQ GEQ '=' NOTEQUAL '#' IN
-%left OR
-%left AND '&'
+%left OROR
+%left LOGICAL_AND '&'
 %left '@'
 %left '+' '-'
 %left '*' '/' DIV MOD
@@ -147,6 +185,8 @@ char *make_qualname();
 /* This is not an actual token ; it is used for precedence. 
 %right QID
 */
+
+\f
 %%
 
 start   :      exp
@@ -177,7 +217,7 @@ exp :       '+' exp    %prec UNARY
        ;
 
 exp    :       not_exp exp %prec UNARY
-                       { write_exp_elt_opcode (UNOP_ZEROP); }
+                       { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
        ;
 
 not_exp        :       NOT
@@ -200,13 +240,13 @@ exp       :       HIGH '(' exp ')'
                        { 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); }
@@ -293,9 +333,9 @@ exp     :       exp '['
                           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 '('
@@ -404,16 +444,12 @@ exp       :       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
@@ -423,13 +459,13 @@ 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); }
@@ -565,10 +601,25 @@ variable: NAME
                                case LOC_REGISTER:
                                case LOC_ARG:
                                case LOC_LOCAL:
+                               case LOC_REF_ARG:
+                               case LOC_REGPARM:
+                               case LOC_LOCAL_ARG:
                                  if (innermost_block == 0 ||
                                      contained_in (block_found,
                                                    innermost_block))
                                    innermost_block = block_found;
+                                 break;
+
+                               case LOC_UNDEF:
+                               case LOC_CONST:
+                               case LOC_STATIC:
+                               case LOC_TYPEDEF:
+                               case LOC_LABEL: /* maybe should go above? */
+                               case LOC_BLOCK:
+                               case LOC_CONST_BYTES:
+                                 /* These are listed so gcc -Wall will reveal
+                                    un-handled cases.  */
+                                 break;
                                }
                              write_exp_elt_opcode (OP_VAR_VALUE);
                              write_exp_elt_sym (sym);
@@ -576,34 +627,28 @@ variable: NAME
                            }
                          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,
+                                         (struct objfile *) 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_longcst ((LONGEST) SYMBOL_VALUE_ADDRESS (msymbol));
                                  write_exp_elt_opcode (OP_LONG);
                                  write_exp_elt_opcode (UNOP_MEMVAL);
-                                 if (mft == mf_data || mft == mf_bss)
+                                 if (msymbol -> type == mst_data ||
+                                     msymbol -> type == mst_bss)
                                    write_exp_elt_type (builtin_type_int);
-                                 else if (mft == mf_text)
+                                 else if (msymbol -> type == mst_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);
                                }
-                             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.",
@@ -653,11 +698,8 @@ parse_number (olen)
   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;
@@ -748,11 +790,11 @@ static struct
    int token;
 } tokentab2[] =
 {
-    {"<>",    NOTEQUAL          },
-    {":=",    ASSIGN    },
-    {"<=",    LEQ       },
-    {">=",    GEQ       },
-    {"::",    COLONCOLON },
+    { {'<', '>'},    NOTEQUAL  },
+    { {':', '='},    ASSIGN    },
+    { {'<', '='},    LEQ       },
+    { {'>', '='},    GEQ       },
+    { {':', ':'},    COLONCOLON },
 
 };
 
@@ -765,17 +807,17 @@ struct keyword {
 
 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       },
@@ -811,7 +853,7 @@ yylex ()
 
   /* 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))
+     if(STREQN(tokentab2[i].name, tokstart, 2))
      {
        lexptr += 2;
        return tokentab2[i].token;
@@ -936,7 +978,7 @@ yylex ()
          {
            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);
          }
@@ -1006,14 +1048,14 @@ yylex ()
   if (*tokstart == '$') {
     for (c = 0; c < NUM_REGS; c++)
       if (namelen - 1 == strlen (reg_names[c])
-         && !strncmp (tokstart + 1, reg_names[c], namelen - 1))
+         && STREQN (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))
+        && STREQN (tokstart + 1, std_regs[c].name, namelen - 1))
        {
         yylval.lval = std_regs[c].regnum;
         return REGNAME;
@@ -1023,7 +1065,7 @@ yylex ()
 
   /*  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))
+     if(namelen == strlen(keytab[i].keyw) && STREQN(tokstart,keytab[i].keyw,namelen))
           return keytab[i].token;
 
   yylval.sval.ptr = tokstart;
@@ -1089,15 +1131,15 @@ yylex ()
     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;
        }
     }
 
@@ -1106,21 +1148,23 @@ yylex ()
  }
 }
 
-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()
+yyerror(msg)
+     char *msg;        /* unused */
 {
    printf("Parsing:  %s\n",lexptr);
    if (yychar < 256)
@@ -1128,91 +1172,4 @@ yyerror()
    else
      error("Invalid syntax in expression");
 }
-\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[]) = 
-{
-  &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
-};
-
-/* 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);
-}
This page took 0.030007 seconds and 4 git commands to generate.