]> git.ipfire.org Git - thirdparty/binutils-gdb.git/commitdiff
2001-11-06 Pierre Muller <muller@ics.u-strasbg.fr>
authorPierre Muller <muller@sourceware.org>
Fri, 9 Nov 2001 09:18:15 +0000 (09:18 +0000)
committerPierre Muller <muller@sourceware.org>
Fri, 9 Nov 2001 09:18:15 +0000 (09:18 +0000)
* p-exp.y (yylex): Only change case of expression if symbol is found.
Also check for GPC standard name form.

gdb/ChangeLog
gdb/p-exp.y

index 86a88386d8c0f138e32902011e6963865338f811..48c619d463279566e292881b805df994d6922016 100644 (file)
@@ -1,3 +1,8 @@
+2001-11-06 Pierre Muller  <muller@ics.u-strasbg.fr>
+
+       * p-exp.y (yylex): Only change case of expression if symbol is found.
+       Also check for GPC standard name form.
+
 2001-11-02  Andrew Cagney  <ac131313@redhat.com>
 
        * utils.c (internal_verror): Restore calls to abort().
index d786af9f6e0efb5374458d2c2316e8d7ac8ca250..ab1622e787d2dec1ef2c551a2464719200c094f4 100644 (file)
-/* YACC parser for Pascal expressions, for GDB.
-   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-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
-
-\f
-%%
-
-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
-    {
-      int shift;
-      if (sizeof (ULONGEST) * HOST_CHAR_BIT < TARGET_LONG_LONG_BIT)
-       /* A long long does not fit in a LONGEST.  */
-       shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
-      else
-       shift = (TARGET_LONG_LONG_BIT - 1);
-      high_bit = (ULONGEST) 1 << shift;
-      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 explen, tempbufindex;
-  static char *tempbuf;
-  static int tempbufsize;
-
- retry:
-
-  tokstart = lexptr;
-  explen = strlen (lexptr);
-  /* See if it is a special token of length 3.  */
-  if (explen > 2)
-    for (i = 0; i < sizeof (tokentab3) / sizeof (tokentab3[0]); i++)
-      if (strncasecmp (tokstart, tokentab3[i].operator, 3) == 0
-          && (!isalpha (tokentab3[i].operator[0]) || explen == 3
-              || (!isalpha (tokstart[3]) && !isdigit (tokstart[3]) && tokstart[3] != '_')))
-        {
-          lexptr += 3;
-          yylval.opcode = tokentab3[i].opcode;
-          return tokentab3[i].token;
-        }
-
-  /* See if it is a special token of length 2.  */
-  if (explen > 1)
-  for (i = 0; i < sizeof (tokentab2) / sizeof (tokentab2[0]); i++)
-      if (strncasecmp (tokstart, tokentab2[i].operator, 2) == 0
-          && (!isalpha (tokentab2[i].operator[0]) || explen == 2
-              || (!isalpha (tokstart[2]) && !isdigit (tokstart[2]) && tokstart[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);
-}
+/* YACC parser for Pascal expressions, for GDB.\r
+   Copyright 2000\r
+   Free Software Foundation, Inc.\r
+\r
+This file is part of GDB.\r
+\r
+This program is free software; you can redistribute it and/or modify\r
+it under the terms of the GNU General Public License as published by\r
+the Free Software Foundation; either version 2 of the License, or\r
+(at your option) any later version.\r
+\r
+This program is distributed in the hope that it will be useful,\r
+but WITHOUT ANY WARRANTY; without even the implied warranty of\r
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the\r
+GNU General Public License for more details.\r
+\r
+You should have received a copy of the GNU General Public License\r
+along with this program; if not, write to the Free Software\r
+Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.  */\r
+\r
+/* This file is derived from c-exp.y */\r
+\r
+/* Parse a Pascal expression from text in a string,\r
+   and return the result as a  struct expression  pointer.\r
+   That structure contains arithmetic operations in reverse polish,\r
+   with constants represented by operations that are followed by special data.\r
+   See expression.h for the details of the format.\r
+   What is important here is that it can be built up sequentially\r
+   during the process of parsing; the lower levels of the tree always\r
+   come first in the result.\r
+\r
+   Note that malloc's and realloc's in this file are transformed to\r
+   xmalloc and xrealloc respectively by the same sed command in the\r
+   makefile that remaps any other malloc/realloc inserted by the parser\r
+   generator.  Doing this with #defines and trying to control the interaction\r
+   with include files (<malloc.h> and <stdlib.h> for example) just became\r
+   too messy, particularly when such includes can be inserted at random\r
+   times by the parser generator.  */\r
+\r
+/* FIXME: there are still 21 shift/reduce conflicts\r
+   Other known bugs or limitations:\r
+    - pascal string operations are not supported at all.\r
+    - there are some problems with boolean types.\r
+    - Pascal type hexadecimal constants are not supported\r
+      because they conflict with the internal variables format.\r
+   Probably also lots of other problems, less well defined PM */\r
+%{\r
+\r
+#include "defs.h"\r
+#include "gdb_string.h"\r
+#include <ctype.h>\r
+#include "expression.h"\r
+#include "value.h"\r
+#include "parser-defs.h"\r
+#include "language.h"\r
+#include "p-lang.h"\r
+#include "bfd.h" /* Required by objfiles.h.  */\r
+#include "symfile.h" /* Required by objfiles.h.  */\r
+#include "objfiles.h" /* For have_full_symbols and have_partial_symbols */\r
+\r
+/* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),\r
+   as well as gratuitiously global symbol names, so we can have multiple\r
+   yacc generated parsers in gdb.  Note that these are only the variables\r
+   produced by yacc.  If other parser generators (bison, byacc, etc) produce\r
+   additional global names that conflict at link time, then those parser\r
+   generators need to be fixed instead of adding those names to this list. */\r
+\r
+#define        yymaxdepth pascal_maxdepth\r
+#define        yyparse pascal_parse\r
+#define        yylex   pascal_lex\r
+#define        yyerror pascal_error\r
+#define        yylval  pascal_lval\r
+#define        yychar  pascal_char\r
+#define        yydebug pascal_debug\r
+#define        yypact  pascal_pact     \r
+#define        yyr1    pascal_r1                       \r
+#define        yyr2    pascal_r2                       \r
+#define        yydef   pascal_def              \r
+#define        yychk   pascal_chk              \r
+#define        yypgo   pascal_pgo              \r
+#define        yyact   pascal_act\r
+#define        yyexca  pascal_exca\r
+#define yyerrflag pascal_errflag\r
+#define yynerrs        pascal_nerrs\r
+#define        yyps    pascal_ps\r
+#define        yypv    pascal_pv\r
+#define        yys     pascal_s\r
+#define        yy_yys  pascal_yys\r
+#define        yystate pascal_state\r
+#define        yytmp   pascal_tmp\r
+#define        yyv     pascal_v\r
+#define        yy_yyv  pascal_yyv\r
+#define        yyval   pascal_val\r
+#define        yylloc  pascal_lloc\r
+#define yyreds pascal_reds             /* With YYDEBUG defined */\r
+#define yytoks pascal_toks             /* With YYDEBUG defined */\r
+#define yylhs  pascal_yylhs\r
+#define yylen  pascal_yylen\r
+#define yydefred pascal_yydefred\r
+#define yydgoto        pascal_yydgoto\r
+#define yysindex pascal_yysindex\r
+#define yyrindex pascal_yyrindex\r
+#define yygindex pascal_yygindex\r
+#define yytable         pascal_yytable\r
+#define yycheck         pascal_yycheck\r
+\r
+#ifndef YYDEBUG\r
+#define        YYDEBUG 0               /* Default to no yydebug support */\r
+#endif\r
+\r
+int yyparse (void);\r
+\r
+static int yylex (void);\r
+\r
+void\r
+yyerror (char *);\r
+\r
+static char * uptok (char *, int);\r
+%}\r
+\r
+/* Although the yacc "value" of an expression is not used,\r
+   since the result is stored in the structure being created,\r
+   other node types do have values.  */\r
+\r
+%union\r
+  {\r
+    LONGEST lval;\r
+    struct {\r
+      LONGEST val;\r
+      struct type *type;\r
+    } typed_val_int;\r
+    struct {\r
+      DOUBLEST dval;\r
+      struct type *type;\r
+    } typed_val_float;\r
+    struct symbol *sym;\r
+    struct type *tval;\r
+    struct stoken sval;\r
+    struct ttype tsym;\r
+    struct symtoken ssym;\r
+    int voidval;\r
+    struct block *bval;\r
+    enum exp_opcode opcode;\r
+    struct internalvar *ivar;\r
+\r
+    struct type **tvec;\r
+    int *ivec;\r
+  }\r
+\r
+%{\r
+/* YYSTYPE gets defined by %union */\r
+static int\r
+parse_number (char *, int, int, YYSTYPE *);\r
+%}\r
+\r
+%type <voidval> exp exp1 type_exp start variable qualified_name\r
+%type <tval> type typebase\r
+/* %type <bval> block */\r
+\r
+/* Fancy type parsing.  */\r
+%type <tval> ptype\r
+\r
+%token <typed_val_int> INT\r
+%token <typed_val_float> FLOAT\r
+\r
+/* Both NAME and TYPENAME tokens represent symbols in the input,\r
+   and both convey their data as strings.\r
+   But a TYPENAME is a string that happens to be defined as a typedef\r
+   or builtin type name (such as int or char)\r
+   and a NAME is any other symbol.\r
+   Contexts where this distinction is not important can use the\r
+   nonterminal "name", which matches either NAME or TYPENAME.  */\r
+\r
+%token <sval> STRING\r
+%token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */\r
+%token <tsym> TYPENAME\r
+%type <sval> name\r
+%type <ssym> name_not_typename\r
+\r
+/* A NAME_OR_INT is a symbol which is not known in the symbol table,\r
+   but which would parse as a valid number in the current input radix.\r
+   E.g. "c" when input_radix==16.  Depending on the parse, it will be\r
+   turned into a name or into a number.  */\r
+\r
+%token <ssym> NAME_OR_INT\r
+\r
+%token STRUCT CLASS SIZEOF COLONCOLON\r
+%token ERROR\r
+\r
+/* Special type cases, put in to allow the parser to distinguish different\r
+   legal basetypes.  */\r
+\r
+%token <voidval> VARIABLE\r
+\r
+\r
+/* Object pascal */\r
+%token THIS\r
+%token <lval> TRUE FALSE\r
+\r
+%left ','\r
+%left ABOVE_COMMA\r
+%right ASSIGN\r
+%left NOT\r
+%left OR\r
+%left XOR\r
+%left ANDAND\r
+%left '=' NOTEQUAL\r
+%left '<' '>' LEQ GEQ\r
+%left LSH RSH DIV MOD\r
+%left '@'\r
+%left '+' '-'\r
+%left '*' '/'\r
+%right UNARY INCREMENT DECREMENT\r
+%right ARROW '.' '[' '('\r
+%token <ssym> BLOCKNAME\r
+%type <bval> block\r
+%left COLONCOLON\r
+\r
+\f\r
+%%\r
+\r
+start   :      exp1\r
+       |       type_exp\r
+       ;\r
+\r
+type_exp:      type\r
+                       { write_exp_elt_opcode(OP_TYPE);\r
+                         write_exp_elt_type($1);\r
+                         write_exp_elt_opcode(OP_TYPE);}\r
+       ;\r
+\r
+/* Expressions, including the comma operator.  */\r
+exp1   :       exp\r
+       |       exp1 ',' exp\r
+                       { write_exp_elt_opcode (BINOP_COMMA); }\r
+       ;\r
+\r
+/* Expressions, not including the comma operator.  */\r
+exp    :       exp '^'   %prec UNARY\r
+                       { write_exp_elt_opcode (UNOP_IND); }\r
+\r
+exp    :       '@' exp    %prec UNARY\r
+                       { write_exp_elt_opcode (UNOP_ADDR); }\r
+\r
+exp    :       '-' exp    %prec UNARY\r
+                       { write_exp_elt_opcode (UNOP_NEG); }\r
+       ;\r
+\r
+exp    :       NOT exp    %prec UNARY\r
+                       { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }\r
+       ;\r
+\r
+exp    :       INCREMENT '(' exp ')'   %prec UNARY\r
+                       { write_exp_elt_opcode (UNOP_PREINCREMENT); }\r
+       ;\r
+\r
+exp    :       DECREMENT  '(' exp ')'   %prec UNARY\r
+                       { write_exp_elt_opcode (UNOP_PREDECREMENT); }\r
+       ;\r
+\r
+exp    :       exp '.' name\r
+                       { write_exp_elt_opcode (STRUCTOP_STRUCT);\r
+                         write_exp_string ($3);\r
+                         write_exp_elt_opcode (STRUCTOP_STRUCT); }\r
+       ;\r
+\r
+exp    :       exp '[' exp1 ']'\r
+                       { write_exp_elt_opcode (BINOP_SUBSCRIPT); }\r
+       ;\r
+\r
+exp    :       exp '('\r
+                       /* This is to save the value of arglist_len\r
+                          being accumulated by an outer function call.  */\r
+                       { start_arglist (); }\r
+               arglist ')'     %prec ARROW\r
+                       { write_exp_elt_opcode (OP_FUNCALL);\r
+                         write_exp_elt_longcst ((LONGEST) end_arglist ());\r
+                         write_exp_elt_opcode (OP_FUNCALL); }\r
+       ;\r
+\r
+arglist        :\r
+         | exp\r
+                       { arglist_len = 1; }\r
+        | arglist ',' exp   %prec ABOVE_COMMA\r
+                       { arglist_len++; }\r
+       ;\r
+\r
+exp    :       type '(' exp ')' %prec UNARY\r
+                       { write_exp_elt_opcode (UNOP_CAST);\r
+                         write_exp_elt_type ($1);\r
+                         write_exp_elt_opcode (UNOP_CAST); }\r
+       ;\r
+\r
+exp    :       '(' exp1 ')'\r
+                       { }\r
+       ;\r
+\r
+/* Binary operators in order of decreasing precedence.  */\r
+\r
+exp    :       exp '*' exp\r
+                       { write_exp_elt_opcode (BINOP_MUL); }\r
+       ;\r
+\r
+exp    :       exp '/' exp\r
+                       { write_exp_elt_opcode (BINOP_DIV); }\r
+       ;\r
+\r
+exp    :       exp DIV exp\r
+                       { write_exp_elt_opcode (BINOP_INTDIV); }\r
+       ;\r
+\r
+exp    :       exp MOD exp\r
+                       { write_exp_elt_opcode (BINOP_REM); }\r
+       ;\r
+\r
+exp    :       exp '+' exp\r
+                       { write_exp_elt_opcode (BINOP_ADD); }\r
+       ;\r
+\r
+exp    :       exp '-' exp\r
+                       { write_exp_elt_opcode (BINOP_SUB); }\r
+       ;\r
+\r
+exp    :       exp LSH exp\r
+                       { write_exp_elt_opcode (BINOP_LSH); }\r
+       ;\r
+\r
+exp    :       exp RSH exp\r
+                       { write_exp_elt_opcode (BINOP_RSH); }\r
+       ;\r
+\r
+exp    :       exp '=' exp\r
+                       { write_exp_elt_opcode (BINOP_EQUAL); }\r
+       ;\r
+\r
+exp    :       exp NOTEQUAL exp\r
+                       { write_exp_elt_opcode (BINOP_NOTEQUAL); }\r
+       ;\r
+\r
+exp    :       exp LEQ exp\r
+                       { write_exp_elt_opcode (BINOP_LEQ); }\r
+       ;\r
+\r
+exp    :       exp GEQ exp\r
+                       { write_exp_elt_opcode (BINOP_GEQ); }\r
+       ;\r
+\r
+exp    :       exp '<' exp\r
+                       { write_exp_elt_opcode (BINOP_LESS); }\r
+       ;\r
+\r
+exp    :       exp '>' exp\r
+                       { write_exp_elt_opcode (BINOP_GTR); }\r
+       ;\r
+\r
+exp    :       exp ANDAND exp\r
+                       { write_exp_elt_opcode (BINOP_BITWISE_AND); }\r
+       ;\r
+\r
+exp    :       exp XOR exp\r
+                       { write_exp_elt_opcode (BINOP_BITWISE_XOR); }\r
+       ;\r
+\r
+exp    :       exp OR exp\r
+                       { write_exp_elt_opcode (BINOP_BITWISE_IOR); }\r
+       ;\r
+\r
+exp    :       exp ASSIGN exp\r
+                       { write_exp_elt_opcode (BINOP_ASSIGN); }\r
+       ;\r
+\r
+exp    :       TRUE\r
+                       { write_exp_elt_opcode (OP_BOOL);\r
+                         write_exp_elt_longcst ((LONGEST) $1);\r
+                         write_exp_elt_opcode (OP_BOOL); }\r
+       ;\r
+\r
+exp    :       FALSE\r
+                       { write_exp_elt_opcode (OP_BOOL);\r
+                         write_exp_elt_longcst ((LONGEST) $1);\r
+                         write_exp_elt_opcode (OP_BOOL); }\r
+       ;\r
+\r
+exp    :       INT\r
+                       { write_exp_elt_opcode (OP_LONG);\r
+                         write_exp_elt_type ($1.type);\r
+                         write_exp_elt_longcst ((LONGEST)($1.val));\r
+                         write_exp_elt_opcode (OP_LONG); }\r
+       ;\r
+\r
+exp    :       NAME_OR_INT\r
+                       { YYSTYPE val;\r
+                         parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);\r
+                         write_exp_elt_opcode (OP_LONG);\r
+                         write_exp_elt_type (val.typed_val_int.type);\r
+                         write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);\r
+                         write_exp_elt_opcode (OP_LONG);\r
+                       }\r
+       ;\r
+\r
+\r
+exp    :       FLOAT\r
+                       { write_exp_elt_opcode (OP_DOUBLE);\r
+                         write_exp_elt_type ($1.type);\r
+                         write_exp_elt_dblcst ($1.dval);\r
+                         write_exp_elt_opcode (OP_DOUBLE); }\r
+       ;\r
+\r
+exp    :       variable\r
+       ;\r
+\r
+exp    :       VARIABLE\r
+                       /* Already written by write_dollar_variable. */\r
+       ;\r
+\r
+exp    :       SIZEOF '(' type ')'     %prec UNARY\r
+                       { write_exp_elt_opcode (OP_LONG);\r
+                         write_exp_elt_type (builtin_type_int);\r
+                         CHECK_TYPEDEF ($3);\r
+                         write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));\r
+                         write_exp_elt_opcode (OP_LONG); }\r
+       ;\r
+\r
+exp    :       STRING\r
+                       { /* C strings are converted into array constants with\r
+                            an explicit null byte added at the end.  Thus\r
+                            the array upper bound is the string length.\r
+                            There is no such thing in C as a completely empty\r
+                            string. */\r
+                         char *sp = $1.ptr; int count = $1.length;\r
+                         while (count-- > 0)\r
+                           {\r
+                             write_exp_elt_opcode (OP_LONG);\r
+                             write_exp_elt_type (builtin_type_char);\r
+                             write_exp_elt_longcst ((LONGEST)(*sp++));\r
+                             write_exp_elt_opcode (OP_LONG);\r
+                           }\r
+                         write_exp_elt_opcode (OP_LONG);\r
+                         write_exp_elt_type (builtin_type_char);\r
+                         write_exp_elt_longcst ((LONGEST)'\0');\r
+                         write_exp_elt_opcode (OP_LONG);\r
+                         write_exp_elt_opcode (OP_ARRAY);\r
+                         write_exp_elt_longcst ((LONGEST) 0);\r
+                         write_exp_elt_longcst ((LONGEST) ($1.length));\r
+                         write_exp_elt_opcode (OP_ARRAY); }\r
+       ;\r
+\r
+/* Object pascal  */\r
+exp    :       THIS\r
+                       { write_exp_elt_opcode (OP_THIS);\r
+                         write_exp_elt_opcode (OP_THIS); }\r
+       ;\r
+\r
+/* end of object pascal.  */\r
+\r
+block  :       BLOCKNAME\r
+                       {\r
+                         if ($1.sym != 0)\r
+                             $$ = SYMBOL_BLOCK_VALUE ($1.sym);\r
+                         else\r
+                           {\r
+                             struct symtab *tem =\r
+                                 lookup_symtab (copy_name ($1.stoken));\r
+                             if (tem)\r
+                               $$ = BLOCKVECTOR_BLOCK (BLOCKVECTOR (tem), STATIC_BLOCK);\r
+                             else\r
+                               error ("No file or function \"%s\".",\r
+                                      copy_name ($1.stoken));\r
+                           }\r
+                       }\r
+       ;\r
+\r
+block  :       block COLONCOLON name\r
+                       { struct symbol *tem\r
+                           = lookup_symbol (copy_name ($3), $1,\r
+                                            VAR_NAMESPACE, (int *) NULL,\r
+                                            (struct symtab **) NULL);\r
+                         if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)\r
+                           error ("No function \"%s\" in specified context.",\r
+                                  copy_name ($3));\r
+                         $$ = SYMBOL_BLOCK_VALUE (tem); }\r
+       ;\r
+\r
+variable:      block COLONCOLON name\r
+                       { struct symbol *sym;\r
+                         sym = lookup_symbol (copy_name ($3), $1,\r
+                                              VAR_NAMESPACE, (int *) NULL,\r
+                                              (struct symtab **) NULL);\r
+                         if (sym == 0)\r
+                           error ("No symbol \"%s\" in specified context.",\r
+                                  copy_name ($3));\r
+\r
+                         write_exp_elt_opcode (OP_VAR_VALUE);\r
+                         /* block_found is set by lookup_symbol.  */\r
+                         write_exp_elt_block (block_found);\r
+                         write_exp_elt_sym (sym);\r
+                         write_exp_elt_opcode (OP_VAR_VALUE); }\r
+       ;\r
+\r
+qualified_name:        typebase COLONCOLON name\r
+                       {\r
+                         struct type *type = $1;\r
+                         if (TYPE_CODE (type) != TYPE_CODE_STRUCT\r
+                             && TYPE_CODE (type) != TYPE_CODE_UNION)\r
+                           error ("`%s' is not defined as an aggregate type.",\r
+                                  TYPE_NAME (type));\r
+\r
+                         write_exp_elt_opcode (OP_SCOPE);\r
+                         write_exp_elt_type (type);\r
+                         write_exp_string ($3);\r
+                         write_exp_elt_opcode (OP_SCOPE);\r
+                       }\r
+       ;\r
+\r
+variable:      qualified_name\r
+       |       COLONCOLON name\r
+                       {\r
+                         char *name = copy_name ($2);\r
+                         struct symbol *sym;\r
+                         struct minimal_symbol *msymbol;\r
+\r
+                         sym =\r
+                           lookup_symbol (name, (const struct block *) NULL,\r
+                                          VAR_NAMESPACE, (int *) NULL,\r
+                                          (struct symtab **) NULL);\r
+                         if (sym)\r
+                           {\r
+                             write_exp_elt_opcode (OP_VAR_VALUE);\r
+                             write_exp_elt_block (NULL);\r
+                             write_exp_elt_sym (sym);\r
+                             write_exp_elt_opcode (OP_VAR_VALUE);\r
+                             break;\r
+                           }\r
+\r
+                         msymbol = lookup_minimal_symbol (name, NULL, NULL);\r
+                         if (msymbol != NULL)\r
+                           {\r
+                             write_exp_msymbol (msymbol,\r
+                                                lookup_function_type (builtin_type_int),\r
+                                                builtin_type_int);\r
+                           }\r
+                         else\r
+                           if (!have_full_symbols () && !have_partial_symbols ())\r
+                             error ("No symbol table is loaded.  Use the \"file\" command.");\r
+                           else\r
+                             error ("No symbol \"%s\" in current context.", name);\r
+                       }\r
+       ;\r
+\r
+variable:      name_not_typename\r
+                       { struct symbol *sym = $1.sym;\r
+\r
+                         if (sym)\r
+                           {\r
+                             if (symbol_read_needs_frame (sym))\r
+                               {\r
+                                 if (innermost_block == 0 ||\r
+                                     contained_in (block_found,\r
+                                                   innermost_block))\r
+                                   innermost_block = block_found;\r
+                               }\r
+\r
+                             write_exp_elt_opcode (OP_VAR_VALUE);\r
+                             /* We want to use the selected frame, not\r
+                                another more inner frame which happens to\r
+                                be in the same block.  */\r
+                             write_exp_elt_block (NULL);\r
+                             write_exp_elt_sym (sym);\r
+                             write_exp_elt_opcode (OP_VAR_VALUE);\r
+                           }\r
+                         else if ($1.is_a_field_of_this)\r
+                           {\r
+                             /* Object pascal: it hangs off of `this'.  Must\r
+                                not inadvertently convert from a method call\r
+                                to data ref.  */\r
+                             if (innermost_block == 0 ||\r
+                                 contained_in (block_found, innermost_block))\r
+                               innermost_block = block_found;\r
+                             write_exp_elt_opcode (OP_THIS);\r
+                             write_exp_elt_opcode (OP_THIS);\r
+                             write_exp_elt_opcode (STRUCTOP_PTR);\r
+                             write_exp_string ($1.stoken);\r
+                             write_exp_elt_opcode (STRUCTOP_PTR);\r
+                           }\r
+                         else\r
+                           {\r
+                             struct minimal_symbol *msymbol;\r
+                             register char *arg = copy_name ($1.stoken);\r
+\r
+                             msymbol =\r
+                               lookup_minimal_symbol (arg, NULL, NULL);\r
+                             if (msymbol != NULL)\r
+                               {\r
+                                 write_exp_msymbol (msymbol,\r
+                                                    lookup_function_type (builtin_type_int),\r
+                                                    builtin_type_int);\r
+                               }\r
+                             else if (!have_full_symbols () && !have_partial_symbols ())\r
+                               error ("No symbol table is loaded.  Use the \"file\" command.");\r
+                             else\r
+                               error ("No symbol \"%s\" in current context.",\r
+                                      copy_name ($1.stoken));\r
+                           }\r
+                       }\r
+       ;\r
+\r
+\r
+ptype  :       typebase\r
+       ;\r
+\r
+/* We used to try to recognize more pointer to member types here, but\r
+   that didn't work (shift/reduce conflicts meant that these rules never\r
+   got executed).  The problem is that\r
+     int (foo::bar::baz::bizzle)\r
+   is a function type but\r
+     int (foo::bar::baz::bizzle::*)\r
+   is a pointer to member type.  Stroustrup loses again!  */\r
+\r
+type   :       ptype\r
+       |       typebase COLONCOLON '*'\r
+                       { $$ = lookup_member_type (builtin_type_int, $1); }\r
+       ;\r
+\r
+typebase  /* Implements (approximately): (type-qualifier)* type-specifier */\r
+       :       TYPENAME\r
+                       { $$ = $1.type; }\r
+       |       STRUCT name\r
+                       { $$ = lookup_struct (copy_name ($2),\r
+                                             expression_context_block); }\r
+       |       CLASS name\r
+                       { $$ = lookup_struct (copy_name ($2),\r
+                                             expression_context_block); }\r
+       /* "const" and "volatile" are curently ignored.  A type qualifier\r
+          after the type is handled in the ptype rule.  I think these could\r
+          be too.  */\r
+       ;\r
+\r
+name   :       NAME { $$ = $1.stoken; }\r
+       |       BLOCKNAME { $$ = $1.stoken; }\r
+       |       TYPENAME { $$ = $1.stoken; }\r
+       |       NAME_OR_INT  { $$ = $1.stoken; }\r
+       ;\r
+\r
+name_not_typename :    NAME\r
+       |       BLOCKNAME\r
+/* These would be useful if name_not_typename was useful, but it is just\r
+   a fake for "variable", so these cause reduce/reduce conflicts because\r
+   the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,\r
+   =exp) or just an exp.  If name_not_typename was ever used in an lvalue\r
+   context where only a name could occur, this might be useful.\r
+       |       NAME_OR_INT\r
+ */\r
+       ;\r
+\r
+%%\r
+\r
+/* Take care of parsing a number (anything that starts with a digit).\r
+   Set yylval and return the token type; update lexptr.\r
+   LEN is the number of characters in it.  */\r
+\r
+/*** Needs some error checking for the float case ***/\r
+\r
+static int\r
+parse_number (p, len, parsed_float, putithere)\r
+     register char *p;\r
+     register int len;\r
+     int parsed_float;\r
+     YYSTYPE *putithere;\r
+{\r
+  /* FIXME: Shouldn't these be unsigned?  We don't deal with negative values\r
+     here, and we do kind of silly things like cast to unsigned.  */\r
+  register LONGEST n = 0;\r
+  register LONGEST prevn = 0;\r
+  ULONGEST un;\r
+\r
+  register int i = 0;\r
+  register int c;\r
+  register int base = input_radix;\r
+  int unsigned_p = 0;\r
+\r
+  /* Number of "L" suffixes encountered.  */\r
+  int long_p = 0;\r
+\r
+  /* We have found a "L" or "U" suffix.  */\r
+  int found_suffix = 0;\r
+\r
+  ULONGEST high_bit;\r
+  struct type *signed_type;\r
+  struct type *unsigned_type;\r
+\r
+  if (parsed_float)\r
+    {\r
+      /* It's a float since it contains a point or an exponent.  */\r
+      char c;\r
+      int num = 0;     /* number of tokens scanned by scanf */\r
+      char saved_char = p[len];\r
+\r
+      p[len] = 0;      /* null-terminate the token */\r
+      if (sizeof (putithere->typed_val_float.dval) <= sizeof (float))\r
+       num = sscanf (p, "%g%c", (float *) &putithere->typed_val_float.dval,&c);\r
+      else if (sizeof (putithere->typed_val_float.dval) <= sizeof (double))\r
+       num = sscanf (p, "%lg%c", (double *) &putithere->typed_val_float.dval,&c);\r
+      else\r
+       {\r
+#ifdef SCANF_HAS_LONG_DOUBLE\r
+         num = sscanf (p, "%Lg%c", &putithere->typed_val_float.dval,&c);\r
+#else\r
+         /* Scan it into a double, then assign it to the long double.\r
+            This at least wins with values representable in the range\r
+            of doubles. */\r
+         double temp;\r
+         num = sscanf (p, "%lg%c", &temp,&c);\r
+         putithere->typed_val_float.dval = temp;\r
+#endif\r
+       }\r
+      p[len] = saved_char;     /* restore the input stream */\r
+      if (num != 1)            /* check scanf found ONLY a float ... */\r
+       return ERROR;\r
+      /* See if it has `f' or `l' suffix (float or long double).  */\r
+\r
+      c = tolower (p[len - 1]);\r
+\r
+      if (c == 'f')\r
+       putithere->typed_val_float.type = builtin_type_float;\r
+      else if (c == 'l')\r
+       putithere->typed_val_float.type = builtin_type_long_double;\r
+      else if (isdigit (c) || c == '.')\r
+       putithere->typed_val_float.type = builtin_type_double;\r
+      else\r
+       return ERROR;\r
+\r
+      return FLOAT;\r
+    }\r
+\r
+  /* Handle base-switching prefixes 0x, 0t, 0d, 0 */\r
+  if (p[0] == '0')\r
+    switch (p[1])\r
+      {\r
+      case 'x':\r
+      case 'X':\r
+       if (len >= 3)\r
+         {\r
+           p += 2;\r
+           base = 16;\r
+           len -= 2;\r
+         }\r
+       break;\r
+\r
+      case 't':\r
+      case 'T':\r
+      case 'd':\r
+      case 'D':\r
+       if (len >= 3)\r
+         {\r
+           p += 2;\r
+           base = 10;\r
+           len -= 2;\r
+         }\r
+       break;\r
+\r
+      default:\r
+       base = 8;\r
+       break;\r
+      }\r
+\r
+  while (len-- > 0)\r
+    {\r
+      c = *p++;\r
+      if (c >= 'A' && c <= 'Z')\r
+       c += 'a' - 'A';\r
+      if (c != 'l' && c != 'u')\r
+       n *= base;\r
+      if (c >= '0' && c <= '9')\r
+       {\r
+         if (found_suffix)\r
+           return ERROR;\r
+         n += i = c - '0';\r
+       }\r
+      else\r
+       {\r
+         if (base > 10 && c >= 'a' && c <= 'f')\r
+           {\r
+             if (found_suffix)\r
+               return ERROR;\r
+             n += i = c - 'a' + 10;\r
+           }\r
+         else if (c == 'l')\r
+           {\r
+             ++long_p;\r
+             found_suffix = 1;\r
+           }\r
+         else if (c == 'u')\r
+           {\r
+             unsigned_p = 1;\r
+             found_suffix = 1;\r
+           }\r
+         else\r
+           return ERROR;       /* Char not a digit */\r
+       }\r
+      if (i >= base)\r
+       return ERROR;           /* Invalid digit in this base */\r
+\r
+      /* Portably test for overflow (only works for nonzero values, so make\r
+        a second check for zero).  FIXME: Can't we just make n and prevn\r
+        unsigned and avoid this?  */\r
+      if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)\r
+       unsigned_p = 1;         /* Try something unsigned */\r
+\r
+      /* Portably test for unsigned overflow.\r
+        FIXME: This check is wrong; for example it doesn't find overflow\r
+        on 0x123456789 when LONGEST is 32 bits.  */\r
+      if (c != 'l' && c != 'u' && n != 0)\r
+       {       \r
+         if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))\r
+           error ("Numeric constant too large.");\r
+       }\r
+      prevn = n;\r
+    }\r
+\r
+  /* An integer constant is an int, a long, or a long long.  An L\r
+     suffix forces it to be long; an LL suffix forces it to be long\r
+     long.  If not forced to a larger size, it gets the first type of\r
+     the above that it fits in.  To figure out whether it fits, we\r
+     shift it right and see whether anything remains.  Note that we\r
+     can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one\r
+     operation, because many compilers will warn about such a shift\r
+     (which always produces a zero result).  Sometimes TARGET_INT_BIT\r
+     or TARGET_LONG_BIT will be that big, sometimes not.  To deal with\r
+     the case where it is we just always shift the value more than\r
+     once, with fewer bits each time.  */\r
+\r
+  un = (ULONGEST)n >> 2;\r
+  if (long_p == 0\r
+      && (un >> (TARGET_INT_BIT - 2)) == 0)\r
+    {\r
+      high_bit = ((ULONGEST)1) << (TARGET_INT_BIT-1);\r
+\r
+      /* A large decimal (not hex or octal) constant (between INT_MAX\r
+        and UINT_MAX) is a long or unsigned long, according to ANSI,\r
+        never an unsigned int, but this code treats it as unsigned\r
+        int.  This probably should be fixed.  GCC gives a warning on\r
+        such constants.  */\r
+\r
+      unsigned_type = builtin_type_unsigned_int;\r
+      signed_type = builtin_type_int;\r
+    }\r
+  else if (long_p <= 1\r
+          && (un >> (TARGET_LONG_BIT - 2)) == 0)\r
+    {\r
+      high_bit = ((ULONGEST)1) << (TARGET_LONG_BIT-1);\r
+      unsigned_type = builtin_type_unsigned_long;\r
+      signed_type = builtin_type_long;\r
+    }\r
+  else\r
+    {\r
+      int shift;\r
+      if (sizeof (ULONGEST) * HOST_CHAR_BIT < TARGET_LONG_LONG_BIT)\r
+       /* A long long does not fit in a LONGEST.  */\r
+       shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);\r
+      else\r
+       shift = (TARGET_LONG_LONG_BIT - 1);\r
+      high_bit = (ULONGEST) 1 << shift;\r
+      unsigned_type = builtin_type_unsigned_long_long;\r
+      signed_type = builtin_type_long_long;\r
+    }\r
+\r
+   putithere->typed_val_int.val = n;\r
+\r
+   /* If the high bit of the worked out type is set then this number\r
+      has to be unsigned. */\r
+\r
+   if (unsigned_p || (n & high_bit))\r
+     {\r
+       putithere->typed_val_int.type = unsigned_type;\r
+     }\r
+   else\r
+     {\r
+       putithere->typed_val_int.type = signed_type;\r
+     }\r
+\r
+   return INT;\r
+}\r
+\r
+struct token\r
+{\r
+  char *operator;\r
+  int token;\r
+  enum exp_opcode opcode;\r
+};\r
+\r
+static const struct token tokentab3[] =\r
+  {\r
+    {"shr", RSH, BINOP_END},\r
+    {"shl", LSH, BINOP_END},\r
+    {"and", ANDAND, BINOP_END},\r
+    {"div", DIV, BINOP_END},\r
+    {"not", NOT, BINOP_END},\r
+    {"mod", MOD, BINOP_END},\r
+    {"inc", INCREMENT, BINOP_END},\r
+    {"dec", DECREMENT, BINOP_END},\r
+    {"xor", XOR, BINOP_END}\r
+  };\r
+\r
+static const struct token tokentab2[] =\r
+  {\r
+    {"or", OR, BINOP_END},\r
+    {"<>", NOTEQUAL, BINOP_END},\r
+    {"<=", LEQ, BINOP_END},\r
+    {">=", GEQ, BINOP_END},\r
+    {":=", ASSIGN, BINOP_END}\r
+  };\r
+\r
+/* Allocate uppercased var */\r
+/* make an uppercased copy of tokstart */\r
+static char * uptok (tokstart, namelen)\r
+  char *tokstart;\r
+  int namelen;\r
+{\r
+  int i;\r
+  char *uptokstart = (char *)malloc(namelen+1);\r
+  for (i = 0;i <= namelen;i++)\r
+    {\r
+      if ((tokstart[i]>='a' && tokstart[i]<='z'))\r
+        uptokstart[i] = tokstart[i]-('a'-'A');\r
+      else\r
+        uptokstart[i] = tokstart[i];\r
+    }\r
+  uptokstart[namelen]='\0';\r
+  return uptokstart;\r
+}\r
+/* Read one token, getting characters through lexptr.  */\r
+\r
+\r
+static int\r
+yylex ()\r
+{\r
+  int c;\r
+  int namelen;\r
+  unsigned int i;\r
+  char *tokstart;\r
+  char *uptokstart;\r
+  char *tokptr;\r
+  char *p;\r
+  int explen, tempbufindex;\r
+  static char *tempbuf;\r
+  static int tempbufsize;\r
+\r
+ retry:\r
+\r
+  tokstart = lexptr;\r
+  explen = strlen (lexptr);\r
+  /* See if it is a special token of length 3.  */\r
+  if (explen > 2)\r
+    for (i = 0; i < sizeof (tokentab3) / sizeof (tokentab3[0]); i++)\r
+      if (strncasecmp (tokstart, tokentab3[i].operator, 3) == 0\r
+          && (!isalpha (tokentab3[i].operator[0]) || explen == 3\r
+              || (!isalpha (tokstart[3]) && !isdigit (tokstart[3]) && tokstart[3] != '_')))\r
+        {\r
+          lexptr += 3;\r
+          yylval.opcode = tokentab3[i].opcode;\r
+          return tokentab3[i].token;\r
+        }\r
+\r
+  /* See if it is a special token of length 2.  */\r
+  if (explen > 1)\r
+  for (i = 0; i < sizeof (tokentab2) / sizeof (tokentab2[0]); i++)\r
+      if (strncasecmp (tokstart, tokentab2[i].operator, 2) == 0\r
+          && (!isalpha (tokentab2[i].operator[0]) || explen == 2\r
+              || (!isalpha (tokstart[2]) && !isdigit (tokstart[2]) && tokstart[2] != '_')))\r
+        {\r
+          lexptr += 2;\r
+          yylval.opcode = tokentab2[i].opcode;\r
+          return tokentab2[i].token;\r
+        }\r
+\r
+  switch (c = *tokstart)\r
+    {\r
+    case 0:\r
+      return 0;\r
+\r
+    case ' ':\r
+    case '\t':\r
+    case '\n':\r
+      lexptr++;\r
+      goto retry;\r
+\r
+    case '\'':\r
+      /* We either have a character constant ('0' or '\177' for example)\r
+        or we have a quoted symbol reference ('foo(int,int)' in object pascal\r
+        for example). */\r
+      lexptr++;\r
+      c = *lexptr++;\r
+      if (c == '\\')\r
+       c = parse_escape (&lexptr);\r
+      else if (c == '\'')\r
+       error ("Empty character constant.");\r
+\r
+      yylval.typed_val_int.val = c;\r
+      yylval.typed_val_int.type = builtin_type_char;\r
+\r
+      c = *lexptr++;\r
+      if (c != '\'')\r
+       {\r
+         namelen = skip_quoted (tokstart) - tokstart;\r
+         if (namelen > 2)\r
+           {\r
+             lexptr = tokstart + namelen;\r
+             if (lexptr[-1] != '\'')\r
+               error ("Unmatched single quote.");\r
+             namelen -= 2;\r
+              tokstart++;\r
+              uptokstart = uptok(tokstart,namelen);\r
+             goto tryname;\r
+           }\r
+         error ("Invalid character constant.");\r
+       }\r
+      return INT;\r
+\r
+    case '(':\r
+      paren_depth++;\r
+      lexptr++;\r
+      return c;\r
+\r
+    case ')':\r
+      if (paren_depth == 0)\r
+       return 0;\r
+      paren_depth--;\r
+      lexptr++;\r
+      return c;\r
+\r
+    case ',':\r
+      if (comma_terminates && paren_depth == 0)\r
+       return 0;\r
+      lexptr++;\r
+      return c;\r
+\r
+    case '.':\r
+      /* Might be a floating point number.  */\r
+      if (lexptr[1] < '0' || lexptr[1] > '9')\r
+       goto symbol;            /* Nope, must be a symbol. */\r
+      /* FALL THRU into number case.  */\r
+\r
+    case '0':\r
+    case '1':\r
+    case '2':\r
+    case '3':\r
+    case '4':\r
+    case '5':\r
+    case '6':\r
+    case '7':\r
+    case '8':\r
+    case '9':\r
+      {\r
+       /* It's a number.  */\r
+       int got_dot = 0, got_e = 0, toktype;\r
+       register char *p = tokstart;\r
+       int hex = input_radix > 10;\r
+\r
+       if (c == '0' && (p[1] == 'x' || p[1] == 'X'))\r
+         {\r
+           p += 2;\r
+           hex = 1;\r
+         }\r
+       else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))\r
+         {\r
+           p += 2;\r
+           hex = 0;\r
+         }\r
+\r
+       for (;; ++p)\r
+         {\r
+           /* This test includes !hex because 'e' is a valid hex digit\r
+              and thus does not indicate a floating point number when\r
+              the radix is hex.  */\r
+           if (!hex && !got_e && (*p == 'e' || *p == 'E'))\r
+             got_dot = got_e = 1;\r
+           /* This test does not include !hex, because a '.' always indicates\r
+              a decimal floating point number regardless of the radix.  */\r
+           else if (!got_dot && *p == '.')\r
+             got_dot = 1;\r
+           else if (got_e && (p[-1] == 'e' || p[-1] == 'E')\r
+                    && (*p == '-' || *p == '+'))\r
+             /* This is the sign of the exponent, not the end of the\r
+                number.  */\r
+             continue;\r
+           /* We will take any letters or digits.  parse_number will\r
+              complain if past the radix, or if L or U are not final.  */\r
+           else if ((*p < '0' || *p > '9')\r
+                    && ((*p < 'a' || *p > 'z')\r
+                                 && (*p < 'A' || *p > 'Z')))\r
+             break;\r
+         }\r
+       toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);\r
+        if (toktype == ERROR)\r
+         {\r
+           char *err_copy = (char *) alloca (p - tokstart + 1);\r
+\r
+           memcpy (err_copy, tokstart, p - tokstart);\r
+           err_copy[p - tokstart] = 0;\r
+           error ("Invalid number \"%s\".", err_copy);\r
+         }\r
+       lexptr = p;\r
+       return toktype;\r
+      }\r
+\r
+    case '+':\r
+    case '-':\r
+    case '*':\r
+    case '/':\r
+    case '|':\r
+    case '&':\r
+    case '^':\r
+    case '~':\r
+    case '!':\r
+    case '@':\r
+    case '<':\r
+    case '>':\r
+    case '[':\r
+    case ']':\r
+    case '?':\r
+    case ':':\r
+    case '=':\r
+    case '{':\r
+    case '}':\r
+    symbol:\r
+      lexptr++;\r
+      return c;\r
+\r
+    case '"':\r
+\r
+      /* Build the gdb internal form of the input string in tempbuf,\r
+        translating any standard C escape forms seen.  Note that the\r
+        buffer is null byte terminated *only* for the convenience of\r
+        debugging gdb itself and printing the buffer contents when\r
+        the buffer contains no embedded nulls.  Gdb does not depend\r
+        upon the buffer being null byte terminated, it uses the length\r
+        string instead.  This allows gdb to handle C strings (as well\r
+        as strings in other languages) with embedded null bytes */\r
+\r
+      tokptr = ++tokstart;\r
+      tempbufindex = 0;\r
+\r
+      do {\r
+       /* Grow the static temp buffer if necessary, including allocating\r
+          the first one on demand. */\r
+       if (tempbufindex + 1 >= tempbufsize)\r
+         {\r
+           tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);\r
+         }\r
+       switch (*tokptr)\r
+         {\r
+         case '\0':\r
+         case '"':\r
+           /* Do nothing, loop will terminate. */\r
+           break;\r
+         case '\\':\r
+           tokptr++;\r
+           c = parse_escape (&tokptr);\r
+           if (c == -1)\r
+             {\r
+               continue;\r
+             }\r
+           tempbuf[tempbufindex++] = c;\r
+           break;\r
+         default:\r
+           tempbuf[tempbufindex++] = *tokptr++;\r
+           break;\r
+         }\r
+      } while ((*tokptr != '"') && (*tokptr != '\0'));\r
+      if (*tokptr++ != '"')\r
+       {\r
+         error ("Unterminated string in expression.");\r
+       }\r
+      tempbuf[tempbufindex] = '\0';    /* See note above */\r
+      yylval.sval.ptr = tempbuf;\r
+      yylval.sval.length = tempbufindex;\r
+      lexptr = tokptr;\r
+      return (STRING);\r
+    }\r
+\r
+  if (!(c == '_' || c == '$'\r
+       || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))\r
+    /* We must have come across a bad character (e.g. ';').  */\r
+    error ("Invalid character '%c' in expression.", c);\r
+\r
+  /* It's a name.  See how long it is.  */\r
+  namelen = 0;\r
+  for (c = tokstart[namelen];\r
+       (c == '_' || c == '$' || (c >= '0' && c <= '9')\r
+       || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)\r
+    {\r
+      /* Template parameter lists are part of the name.\r
+        FIXME: This mishandles `print $a<4&&$a>3'.  */\r
+      if (c == '<')\r
+       {\r
+         int i = namelen;\r
+         int nesting_level = 1;\r
+         while (tokstart[++i])\r
+           {\r
+             if (tokstart[i] == '<')\r
+               nesting_level++;\r
+             else if (tokstart[i] == '>')\r
+               {\r
+                 if (--nesting_level == 0)\r
+                   break;\r
+               }\r
+           }\r
+         if (tokstart[i] == '>')\r
+           namelen = i;\r
+         else\r
+           break;\r
+       }\r
+\r
+      /* do NOT uppercase internals because of registers !!! */\r
+      c = tokstart[++namelen];\r
+    }\r
+\r
+  uptokstart = uptok(tokstart,namelen);\r
+\r
+  /* The token "if" terminates the expression and is NOT\r
+     removed from the input stream.  */\r
+  if (namelen == 2 && uptokstart[0] == 'I' && uptokstart[1] == 'F')\r
+    {\r
+      return 0;\r
+    }\r
+\r
+  lexptr += namelen;\r
+\r
+  tryname:\r
+\r
+  /* Catch specific keywords.  Should be done with a data structure.  */\r
+  switch (namelen)\r
+    {\r
+    case 6:\r
+      if (STREQ (uptokstart, "OBJECT"))\r
+       return CLASS;\r
+      if (STREQ (uptokstart, "RECORD"))\r
+       return STRUCT;\r
+      if (STREQ (uptokstart, "SIZEOF"))\r
+       return SIZEOF;\r
+      break;\r
+    case 5:\r
+      if (STREQ (uptokstart, "CLASS"))\r
+       return CLASS;\r
+      if (STREQ (uptokstart, "FALSE"))\r
+       {\r
+          yylval.lval = 0;\r
+          return FALSE;\r
+        }\r
+      break;\r
+    case 4:\r
+      if (STREQ (uptokstart, "TRUE"))\r
+       {\r
+          yylval.lval = 1;\r
+         return TRUE;\r
+        }\r
+      if (STREQ (uptokstart, "SELF"))\r
+        {\r
+          /* here we search for 'this' like\r
+             inserted in FPC stabs debug info */\r
+         static const char this_name[] =\r
+                                { /* CPLUS_MARKER,*/ 't', 'h', 'i', 's', '\0' };\r
+\r
+         if (lookup_symbol (this_name, expression_context_block,\r
+                            VAR_NAMESPACE, (int *) NULL,\r
+                            (struct symtab **) NULL))\r
+           return THIS;\r
+       }\r
+      break;\r
+    default:\r
+      break;\r
+    }\r
+\r
+  yylval.sval.ptr = tokstart;\r
+  yylval.sval.length = namelen;\r
+\r
+  if (*tokstart == '$')\r
+    {\r
+      /* $ is the normal prefix for pascal hexadecimal values\r
+        but this conflicts with the GDB use for debugger variables\r
+        so in expression to enter hexadecimal values\r
+        we still need to use C syntax with 0xff  */\r
+      write_dollar_variable (yylval.sval);\r
+      return VARIABLE;\r
+    }\r
+\r
+  /* Use token-type BLOCKNAME for symbols that happen to be defined as\r
+     functions or symtabs.  If this is not so, then ...\r
+     Use token-type TYPENAME for symbols that happen to be defined\r
+     currently as names of types; NAME for other symbols.\r
+     The caller is not constrained to care about the distinction.  */\r
+  {\r
+    char *tmp = copy_name (yylval.sval);\r
+    struct symbol *sym;\r
+    int is_a_field_of_this = 0;\r
+    int hextype;\r
+\r
+    sym = lookup_symbol (tmp, expression_context_block,\r
+                        VAR_NAMESPACE,\r
+                        &is_a_field_of_this,\r
+                        (struct symtab **) NULL);\r
+    /* second chance uppercased (as Free Pascal does).  */\r
+    if (!sym)\r
+      {\r
+       for (i = 0; i <= namelen; i++)\r
+         {\r
+           if ((tmp[i] >= 'a' && tmp[i] <= 'z'))\r
+             tmp[i] -= ('a'-'A');\r
+         }\r
+       sym = lookup_symbol (tmp, expression_context_block,\r
+                        VAR_NAMESPACE,\r
+                        &is_a_field_of_this,\r
+                        (struct symtab **) NULL);\r
+       if (sym)\r
+         for (i = 0; i <= namelen; i++)\r
+           {\r
+             if ((tokstart[i] >= 'a' && tokstart[i] <= 'z'))\r
+               tokstart[i] -= ('a'-'A');\r
+           }\r
+      }\r
+    /* Third chance Capitalized (as GPC does).  */\r
+    if (!sym)\r
+      {\r
+       for (i = 0; i <= namelen; i++)\r
+         {\r
+           if (i == 0)\r
+             {\r
+              if ((tmp[i] >= 'a' && tmp[i] <= 'z'))\r
+                tmp[i] -= ('a'-'A');\r
+             }\r
+           else\r
+           if ((tmp[i] >= 'A' && tmp[i] <= 'Z'))\r
+             tmp[i] -= ('A'-'a');\r
+          }\r
+       sym = lookup_symbol (tmp, expression_context_block,\r
+                         VAR_NAMESPACE,\r
+                         &is_a_field_of_this,\r
+                         (struct symtab **) NULL);\r
+        if (sym)\r
+          for (i = 0; i <= namelen; i++)\r
+            {\r
+              if (i == 0)\r
+                {\r
+                  if ((tokstart[i] >= 'a' && tokstart[i] <= 'z'))\r
+                    tokstart[i] -= ('a'-'A');\r
+                }\r
+              else\r
+                if ((tokstart[i] >= 'A' && tokstart[i] <= 'Z'))\r
+                  tokstart[i] -= ('A'-'a');\r
+            }\r
+      }\r
+    /* Call lookup_symtab, not lookup_partial_symtab, in case there are\r
+       no psymtabs (coff, xcoff, or some future change to blow away the\r
+       psymtabs once once symbols are read).  */\r
+    if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||\r
+        lookup_symtab (tmp))\r
+      {\r
+       yylval.ssym.sym = sym;\r
+       yylval.ssym.is_a_field_of_this = is_a_field_of_this;\r
+       return BLOCKNAME;\r
+      }\r
+    if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)\r
+        {\r
+#if 1\r
+         /* Despite the following flaw, we need to keep this code enabled.\r
+            Because we can get called from check_stub_method, if we don't\r
+            handle nested types then it screws many operations in any\r
+            program which uses nested types.  */\r
+         /* In "A::x", if x is a member function of A and there happens\r
+            to be a type (nested or not, since the stabs don't make that\r
+            distinction) named x, then this code incorrectly thinks we\r
+            are dealing with nested types rather than a member function.  */\r
+\r
+         char *p;\r
+         char *namestart;\r
+         struct symbol *best_sym;\r
+\r
+         /* Look ahead to detect nested types.  This probably should be\r
+            done in the grammar, but trying seemed to introduce a lot\r
+            of shift/reduce and reduce/reduce conflicts.  It's possible\r
+            that it could be done, though.  Or perhaps a non-grammar, but\r
+            less ad hoc, approach would work well.  */\r
+\r
+         /* Since we do not currently have any way of distinguishing\r
+            a nested type from a non-nested one (the stabs don't tell\r
+            us whether a type is nested), we just ignore the\r
+            containing type.  */\r
+\r
+         p = lexptr;\r
+         best_sym = sym;\r
+         while (1)\r
+           {\r
+             /* Skip whitespace.  */\r
+             while (*p == ' ' || *p == '\t' || *p == '\n')\r
+               ++p;\r
+             if (*p == ':' && p[1] == ':')\r
+               {\r
+                 /* Skip the `::'.  */\r
+                 p += 2;\r
+                 /* Skip whitespace.  */\r
+                 while (*p == ' ' || *p == '\t' || *p == '\n')\r
+                   ++p;\r
+                 namestart = p;\r
+                 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')\r
+                        || (*p >= 'a' && *p <= 'z')\r
+                        || (*p >= 'A' && *p <= 'Z'))\r
+                   ++p;\r
+                 if (p != namestart)\r
+                   {\r
+                     struct symbol *cur_sym;\r
+                     /* As big as the whole rest of the expression, which is\r
+                        at least big enough.  */\r
+                     char *ncopy = alloca (strlen (tmp)+strlen (namestart)+3);\r
+                     char *tmp1;\r
+\r
+                     tmp1 = ncopy;\r
+                     memcpy (tmp1, tmp, strlen (tmp));\r
+                     tmp1 += strlen (tmp);\r
+                     memcpy (tmp1, "::", 2);\r
+                     tmp1 += 2;\r
+                     memcpy (tmp1, namestart, p - namestart);\r
+                     tmp1[p - namestart] = '\0';\r
+                     cur_sym = lookup_symbol (ncopy, expression_context_block,\r
+                                              VAR_NAMESPACE, (int *) NULL,\r
+                                              (struct symtab **) NULL);\r
+                     if (cur_sym)\r
+                       {\r
+                         if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)\r
+                           {\r
+                             best_sym = cur_sym;\r
+                             lexptr = p;\r
+                           }\r
+                         else\r
+                           break;\r
+                       }\r
+                     else\r
+                       break;\r
+                   }\r
+                 else\r
+                   break;\r
+               }\r
+             else\r
+               break;\r
+           }\r
+\r
+         yylval.tsym.type = SYMBOL_TYPE (best_sym);\r
+#else /* not 0 */\r
+         yylval.tsym.type = SYMBOL_TYPE (sym);\r
+#endif /* not 0 */\r
+         return TYPENAME;\r
+        }\r
+    if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)\r
+       return TYPENAME;\r
+\r
+    /* Input names that aren't symbols but ARE valid hex numbers,\r
+       when the input radix permits them, can be names or numbers\r
+       depending on the parse.  Note we support radixes > 16 here.  */\r
+    if (!sym &&\r
+        ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||\r
+         (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))\r
+      {\r
+       YYSTYPE newlval;        /* Its value is ignored.  */\r
+       hextype = parse_number (tokstart, namelen, 0, &newlval);\r
+       if (hextype == INT)\r
+         {\r
+           yylval.ssym.sym = sym;\r
+           yylval.ssym.is_a_field_of_this = is_a_field_of_this;\r
+           return NAME_OR_INT;\r
+         }\r
+      }\r
+\r
+    free(uptokstart);\r
+    /* Any other kind of symbol */\r
+    yylval.ssym.sym = sym;\r
+    yylval.ssym.is_a_field_of_this = is_a_field_of_this;\r
+    return NAME;\r
+  }\r
+}\r
+\r
+void\r
+yyerror (msg)\r
+     char *msg;\r
+{\r
+  error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr);\r
+}\r