1 /* YACC parser for Pascal expressions, for GDB.
3 Free Software Foundation, Inc.
5 This file is part of GDB.
7 This program is free software; you can redistribute it and/or modify
8 it under the terms of the GNU General Public License as published by
9 the Free Software Foundation; either version 2 of the License, or
10 (at your option) any later version.
12 This program is distributed in the hope that it will be useful,
13 but WITHOUT ANY WARRANTY; without even the implied warranty of
14 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15 GNU General Public License for more details.
17 You should have received a copy of the GNU General Public License
18 along with this program; if not, write to the Free Software
19 Foundation, Inc., 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA. */
21 /* This file is derived from c-exp.y */
23 /* Parse a Pascal expression from text in a string,
24 and return the result as a struct expression pointer.
25 That structure contains arithmetic operations in reverse polish,
26 with constants represented by operations that are followed by special data.
27 See expression.h for the details of the format.
28 What is important here is that it can be built up sequentially
29 during the process of parsing; the lower levels of the tree always
30 come first in the result.
32 Note that malloc's and realloc's in this file are transformed to
33 xmalloc and xrealloc respectively by the same sed command in the
34 makefile that remaps any other malloc/realloc inserted by the parser
35 generator. Doing this with #defines and trying to control the interaction
36 with include files (<malloc.h> and <stdlib.h> for example) just became
37 too messy, particularly when such includes can be inserted at random
38 times by the parser generator. */
40 /* FIXME: there are still 21 shift/reduce conflicts
41 Other known bugs or limitations:
42 - pascal string operations are not supported at all.
43 - there are some problems with boolean types.
44 - Pascal type hexadecimal constants are not supported
45 because they conflict with the internal variables format.
46 Probably also lots of other problems, less well defined PM */
50 #include "gdb_string.h"
52 #include "expression.h"
54 #include "parser-defs.h"
57 #include "bfd.h" /* Required by objfiles.h. */
58 #include "symfile.h" /* Required by objfiles.h. */
59 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
61 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
62 as well as gratuitiously global symbol names, so we can have multiple
63 yacc generated parsers in gdb. Note that these are only the variables
64 produced by yacc. If other parser generators (bison, byacc, etc) produce
65 additional global names that conflict at link time, then those parser
66 generators need to be fixed instead of adding those names to this list. */
68 #define yymaxdepth pascal_maxdepth
69 #define yyparse pascal_parse
70 #define yylex pascal_lex
71 #define yyerror pascal_error
72 #define yylval pascal_lval
73 #define yychar pascal_char
74 #define yydebug pascal_debug
75 #define yypact pascal_pact
76 #define yyr1 pascal_r1
77 #define yyr2 pascal_r2
78 #define yydef pascal_def
79 #define yychk pascal_chk
80 #define yypgo pascal_pgo
81 #define yyact pascal_act
82 #define yyexca pascal_exca
83 #define yyerrflag pascal_errflag
84 #define yynerrs pascal_nerrs
85 #define yyps pascal_ps
86 #define yypv pascal_pv
88 #define yy_yys pascal_yys
89 #define yystate pascal_state
90 #define yytmp pascal_tmp
92 #define yy_yyv pascal_yyv
93 #define yyval pascal_val
94 #define yylloc pascal_lloc
95 #define yyreds pascal_reds /* With YYDEBUG defined */
96 #define yytoks pascal_toks /* With YYDEBUG defined */
97 #define yylhs pascal_yylhs
98 #define yylen pascal_yylen
99 #define yydefred pascal_yydefred
100 #define yydgoto pascal_yydgoto
101 #define yysindex pascal_yysindex
102 #define yyrindex pascal_yyrindex
103 #define yygindex pascal_yygindex
104 #define yytable pascal_yytable
105 #define yycheck pascal_yycheck
108 #define YYDEBUG 0 /* Default to no yydebug support */
113 static int yylex (void);
118 static char * uptok (char *, int);
121 /* Although the yacc "value" of an expression is not used,
122 since the result is stored in the structure being created,
123 other node types do have values. */
140 struct symtoken ssym;
143 enum exp_opcode opcode;
144 struct internalvar *ivar;
151 /* YYSTYPE gets defined by %union */
153 parse_number (char *, int, int, YYSTYPE *);
156 %type <voidval> exp exp1 type_exp start variable qualified_name
157 %type <tval> type typebase
158 /* %type <bval> block */
160 /* Fancy type parsing. */
163 %token <typed_val_int> INT
164 %token <typed_val_float> FLOAT
166 /* Both NAME and TYPENAME tokens represent symbols in the input,
167 and both convey their data as strings.
168 But a TYPENAME is a string that happens to be defined as a typedef
169 or builtin type name (such as int or char)
170 and a NAME is any other symbol.
171 Contexts where this distinction is not important can use the
172 nonterminal "name", which matches either NAME or TYPENAME. */
175 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
176 %token <tsym> TYPENAME
178 %type <ssym> name_not_typename
180 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
181 but which would parse as a valid number in the current input radix.
182 E.g. "c" when input_radix==16. Depending on the parse, it will be
183 turned into a name or into a number. */
185 %token <ssym> NAME_OR_INT
187 %token STRUCT CLASS SIZEOF COLONCOLON
190 /* Special type cases, put in to allow the parser to distinguish different
193 %token <voidval> VARIABLE
198 %token <lval> TRUE FALSE
208 %left '<' '>' LEQ GEQ
209 %left LSH RSH DIV MOD
213 %right UNARY INCREMENT DECREMENT
214 %right ARROW '.' '[' '('
215 %token <ssym> BLOCKNAME
227 { write_exp_elt_opcode(OP_TYPE);
228 write_exp_elt_type($1);
229 write_exp_elt_opcode(OP_TYPE);}
232 /* Expressions, including the comma operator. */
235 { write_exp_elt_opcode (BINOP_COMMA); }
238 /* Expressions, not including the comma operator. */
239 exp : exp '^' %prec UNARY
240 { write_exp_elt_opcode (UNOP_IND); }
242 exp : '@' exp %prec UNARY
243 { write_exp_elt_opcode (UNOP_ADDR); }
245 exp : '-' exp %prec UNARY
246 { write_exp_elt_opcode (UNOP_NEG); }
249 exp : NOT exp %prec UNARY
250 { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
253 exp : INCREMENT '(' exp ')' %prec UNARY
254 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
257 exp : DECREMENT '(' exp ')' %prec UNARY
258 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
262 { write_exp_elt_opcode (STRUCTOP_STRUCT);
263 write_exp_string ($3);
264 write_exp_elt_opcode (STRUCTOP_STRUCT); }
267 exp : exp '[' exp1 ']'
268 { write_exp_elt_opcode (BINOP_SUBSCRIPT); }
272 /* This is to save the value of arglist_len
273 being accumulated by an outer function call. */
274 { start_arglist (); }
275 arglist ')' %prec ARROW
276 { write_exp_elt_opcode (OP_FUNCALL);
277 write_exp_elt_longcst ((LONGEST) end_arglist ());
278 write_exp_elt_opcode (OP_FUNCALL); }
284 | arglist ',' exp %prec ABOVE_COMMA
288 exp : type '(' exp ')' %prec UNARY
289 { write_exp_elt_opcode (UNOP_CAST);
290 write_exp_elt_type ($1);
291 write_exp_elt_opcode (UNOP_CAST); }
298 /* Binary operators in order of decreasing precedence. */
301 { write_exp_elt_opcode (BINOP_MUL); }
305 { write_exp_elt_opcode (BINOP_DIV); }
309 { write_exp_elt_opcode (BINOP_INTDIV); }
313 { write_exp_elt_opcode (BINOP_REM); }
317 { write_exp_elt_opcode (BINOP_ADD); }
321 { write_exp_elt_opcode (BINOP_SUB); }
325 { write_exp_elt_opcode (BINOP_LSH); }
329 { write_exp_elt_opcode (BINOP_RSH); }
333 { write_exp_elt_opcode (BINOP_EQUAL); }
336 exp : exp NOTEQUAL exp
337 { write_exp_elt_opcode (BINOP_NOTEQUAL); }
341 { write_exp_elt_opcode (BINOP_LEQ); }
345 { write_exp_elt_opcode (BINOP_GEQ); }
349 { write_exp_elt_opcode (BINOP_LESS); }
353 { write_exp_elt_opcode (BINOP_GTR); }
357 { write_exp_elt_opcode (BINOP_BITWISE_AND); }
361 { write_exp_elt_opcode (BINOP_BITWISE_XOR); }
365 { write_exp_elt_opcode (BINOP_BITWISE_IOR); }
369 { write_exp_elt_opcode (BINOP_ASSIGN); }
373 { write_exp_elt_opcode (OP_BOOL);
374 write_exp_elt_longcst ((LONGEST) $1);
375 write_exp_elt_opcode (OP_BOOL); }
379 { write_exp_elt_opcode (OP_BOOL);
380 write_exp_elt_longcst ((LONGEST) $1);
381 write_exp_elt_opcode (OP_BOOL); }
385 { write_exp_elt_opcode (OP_LONG);
386 write_exp_elt_type ($1.type);
387 write_exp_elt_longcst ((LONGEST)($1.val));
388 write_exp_elt_opcode (OP_LONG); }
393 parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
394 write_exp_elt_opcode (OP_LONG);
395 write_exp_elt_type (val.typed_val_int.type);
396 write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
397 write_exp_elt_opcode (OP_LONG);
403 { write_exp_elt_opcode (OP_DOUBLE);
404 write_exp_elt_type ($1.type);
405 write_exp_elt_dblcst ($1.dval);
406 write_exp_elt_opcode (OP_DOUBLE); }
413 /* Already written by write_dollar_variable. */
416 exp : SIZEOF '(' type ')' %prec UNARY
417 { write_exp_elt_opcode (OP_LONG);
418 write_exp_elt_type (builtin_type_int);
420 write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
421 write_exp_elt_opcode (OP_LONG); }
425 { /* C strings are converted into array constants with
426 an explicit null byte added at the end. Thus
427 the array upper bound is the string length.
428 There is no such thing in C as a completely empty
430 char *sp = $1.ptr; int count = $1.length;
433 write_exp_elt_opcode (OP_LONG);
434 write_exp_elt_type (builtin_type_char);
435 write_exp_elt_longcst ((LONGEST)(*sp++));
436 write_exp_elt_opcode (OP_LONG);
438 write_exp_elt_opcode (OP_LONG);
439 write_exp_elt_type (builtin_type_char);
440 write_exp_elt_longcst ((LONGEST)'\0');
441 write_exp_elt_opcode (OP_LONG);
442 write_exp_elt_opcode (OP_ARRAY);
443 write_exp_elt_longcst ((LONGEST) 0);
444 write_exp_elt_longcst ((LONGEST) ($1.length));
445 write_exp_elt_opcode (OP_ARRAY); }
450 { write_exp_elt_opcode (OP_THIS);
451 write_exp_elt_opcode (OP_THIS); }
454 /* end of object pascal. */
459 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
463 lookup_symtab (copy_name ($1.stoken));
465 $$ = BLOCKVECTOR_BLOCK (BLOCKVECTOR (tem), STATIC_BLOCK);
467 error ("No file or function \"%s\".",
468 copy_name ($1.stoken));
473 block : block COLONCOLON name
475 = lookup_symbol (copy_name ($3), $1,
476 VAR_NAMESPACE, (int *) NULL,
477 (struct symtab **) NULL);
478 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
479 error ("No function \"%s\" in specified context.",
481 $$ = SYMBOL_BLOCK_VALUE (tem); }
484 variable: block COLONCOLON name
485 { struct symbol *sym;
486 sym = lookup_symbol (copy_name ($3), $1,
487 VAR_NAMESPACE, (int *) NULL,
488 (struct symtab **) NULL);
490 error ("No symbol \"%s\" in specified context.",
493 write_exp_elt_opcode (OP_VAR_VALUE);
494 /* block_found is set by lookup_symbol. */
495 write_exp_elt_block (block_found);
496 write_exp_elt_sym (sym);
497 write_exp_elt_opcode (OP_VAR_VALUE); }
500 qualified_name: typebase COLONCOLON name
502 struct type *type = $1;
503 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
504 && TYPE_CODE (type) != TYPE_CODE_UNION)
505 error ("`%s' is not defined as an aggregate type.",
508 write_exp_elt_opcode (OP_SCOPE);
509 write_exp_elt_type (type);
510 write_exp_string ($3);
511 write_exp_elt_opcode (OP_SCOPE);
515 variable: qualified_name
518 char *name = copy_name ($2);
520 struct minimal_symbol *msymbol;
523 lookup_symbol (name, (const struct block *) NULL,
524 VAR_NAMESPACE, (int *) NULL,
525 (struct symtab **) NULL);
528 write_exp_elt_opcode (OP_VAR_VALUE);
529 write_exp_elt_block (NULL);
530 write_exp_elt_sym (sym);
531 write_exp_elt_opcode (OP_VAR_VALUE);
535 msymbol = lookup_minimal_symbol (name, NULL, NULL);
538 write_exp_msymbol (msymbol,
539 lookup_function_type (builtin_type_int),
543 if (!have_full_symbols () && !have_partial_symbols ())
544 error ("No symbol table is loaded. Use the \"file\" command.");
546 error ("No symbol \"%s\" in current context.", name);
550 variable: name_not_typename
551 { struct symbol *sym = $1.sym;
555 if (symbol_read_needs_frame (sym))
557 if (innermost_block == 0 ||
558 contained_in (block_found,
560 innermost_block = block_found;
563 write_exp_elt_opcode (OP_VAR_VALUE);
564 /* We want to use the selected frame, not
565 another more inner frame which happens to
566 be in the same block. */
567 write_exp_elt_block (NULL);
568 write_exp_elt_sym (sym);
569 write_exp_elt_opcode (OP_VAR_VALUE);
571 else if ($1.is_a_field_of_this)
573 /* Object pascal: it hangs off of `this'. Must
574 not inadvertently convert from a method call
576 if (innermost_block == 0 ||
577 contained_in (block_found, innermost_block))
578 innermost_block = block_found;
579 write_exp_elt_opcode (OP_THIS);
580 write_exp_elt_opcode (OP_THIS);
581 write_exp_elt_opcode (STRUCTOP_PTR);
582 write_exp_string ($1.stoken);
583 write_exp_elt_opcode (STRUCTOP_PTR);
587 struct minimal_symbol *msymbol;
588 register char *arg = copy_name ($1.stoken);
591 lookup_minimal_symbol (arg, NULL, NULL);
594 write_exp_msymbol (msymbol,
595 lookup_function_type (builtin_type_int),
598 else if (!have_full_symbols () && !have_partial_symbols ())
599 error ("No symbol table is loaded. Use the \"file\" command.");
601 error ("No symbol \"%s\" in current context.",
602 copy_name ($1.stoken));
611 /* We used to try to recognize more pointer to member types here, but
612 that didn't work (shift/reduce conflicts meant that these rules never
613 got executed). The problem is that
614 int (foo::bar::baz::bizzle)
615 is a function type but
616 int (foo::bar::baz::bizzle::*)
617 is a pointer to member type. Stroustrup loses again! */
620 | typebase COLONCOLON '*'
621 { $$ = lookup_member_type (builtin_type_int, $1); }
624 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
628 { $$ = lookup_struct (copy_name ($2),
629 expression_context_block); }
631 { $$ = lookup_struct (copy_name ($2),
632 expression_context_block); }
633 /* "const" and "volatile" are curently ignored. A type qualifier
634 after the type is handled in the ptype rule. I think these could
638 name : NAME { $$ = $1.stoken; }
639 | BLOCKNAME { $$ = $1.stoken; }
640 | TYPENAME { $$ = $1.stoken; }
641 | NAME_OR_INT { $$ = $1.stoken; }
644 name_not_typename : NAME
646 /* These would be useful if name_not_typename was useful, but it is just
647 a fake for "variable", so these cause reduce/reduce conflicts because
648 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
649 =exp) or just an exp. If name_not_typename was ever used in an lvalue
650 context where only a name could occur, this might be useful.
657 /* Take care of parsing a number (anything that starts with a digit).
658 Set yylval and return the token type; update lexptr.
659 LEN is the number of characters in it. */
661 /*** Needs some error checking for the float case ***/
664 parse_number (p, len, parsed_float, putithere)
670 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
671 here, and we do kind of silly things like cast to unsigned. */
672 register LONGEST n = 0;
673 register LONGEST prevn = 0;
678 register int base = input_radix;
681 /* Number of "L" suffixes encountered. */
684 /* We have found a "L" or "U" suffix. */
685 int found_suffix = 0;
688 struct type *signed_type;
689 struct type *unsigned_type;
693 /* It's a float since it contains a point or an exponent. */
695 int num = 0; /* number of tokens scanned by scanf */
696 char saved_char = p[len];
698 p[len] = 0; /* null-terminate the token */
699 if (sizeof (putithere->typed_val_float.dval) <= sizeof (float))
700 num = sscanf (p, "%g%c", (float *) &putithere->typed_val_float.dval,&c);
701 else if (sizeof (putithere->typed_val_float.dval) <= sizeof (double))
702 num = sscanf (p, "%lg%c", (double *) &putithere->typed_val_float.dval,&c);
705 #ifdef SCANF_HAS_LONG_DOUBLE
706 num = sscanf (p, "%Lg%c", &putithere->typed_val_float.dval,&c);
708 /* Scan it into a double, then assign it to the long double.
709 This at least wins with values representable in the range
712 num = sscanf (p, "%lg%c", &temp,&c);
713 putithere->typed_val_float.dval = temp;
716 p[len] = saved_char; /* restore the input stream */
717 if (num != 1) /* check scanf found ONLY a float ... */
719 /* See if it has `f' or `l' suffix (float or long double). */
721 c = tolower (p[len - 1]);
724 putithere->typed_val_float.type = builtin_type_float;
726 putithere->typed_val_float.type = builtin_type_long_double;
727 else if (isdigit (c) || c == '.')
728 putithere->typed_val_float.type = builtin_type_double;
735 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
769 if (c >= 'A' && c <= 'Z')
771 if (c != 'l' && c != 'u')
773 if (c >= '0' && c <= '9')
781 if (base > 10 && c >= 'a' && c <= 'f')
785 n += i = c - 'a' + 10;
798 return ERROR; /* Char not a digit */
801 return ERROR; /* Invalid digit in this base */
803 /* Portably test for overflow (only works for nonzero values, so make
804 a second check for zero). FIXME: Can't we just make n and prevn
805 unsigned and avoid this? */
806 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
807 unsigned_p = 1; /* Try something unsigned */
809 /* Portably test for unsigned overflow.
810 FIXME: This check is wrong; for example it doesn't find overflow
811 on 0x123456789 when LONGEST is 32 bits. */
812 if (c != 'l' && c != 'u' && n != 0)
814 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
815 error ("Numeric constant too large.");
820 /* An integer constant is an int, a long, or a long long. An L
821 suffix forces it to be long; an LL suffix forces it to be long
822 long. If not forced to a larger size, it gets the first type of
823 the above that it fits in. To figure out whether it fits, we
824 shift it right and see whether anything remains. Note that we
825 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
826 operation, because many compilers will warn about such a shift
827 (which always produces a zero result). Sometimes TARGET_INT_BIT
828 or TARGET_LONG_BIT will be that big, sometimes not. To deal with
829 the case where it is we just always shift the value more than
830 once, with fewer bits each time. */
832 un = (ULONGEST)n >> 2;
834 && (un >> (TARGET_INT_BIT - 2)) == 0)
836 high_bit = ((ULONGEST)1) << (TARGET_INT_BIT-1);
838 /* A large decimal (not hex or octal) constant (between INT_MAX
839 and UINT_MAX) is a long or unsigned long, according to ANSI,
840 never an unsigned int, but this code treats it as unsigned
841 int. This probably should be fixed. GCC gives a warning on
844 unsigned_type = builtin_type_unsigned_int;
845 signed_type = builtin_type_int;
848 && (un >> (TARGET_LONG_BIT - 2)) == 0)
850 high_bit = ((ULONGEST)1) << (TARGET_LONG_BIT-1);
851 unsigned_type = builtin_type_unsigned_long;
852 signed_type = builtin_type_long;
856 high_bit = (((ULONGEST)1)
857 << (TARGET_LONG_LONG_BIT - 32 - 1)
861 /* A long long does not fit in a LONGEST. */
863 (ULONGEST)1 << (sizeof (LONGEST) * HOST_CHAR_BIT - 1);
864 unsigned_type = builtin_type_unsigned_long_long;
865 signed_type = builtin_type_long_long;
868 putithere->typed_val_int.val = n;
870 /* If the high bit of the worked out type is set then this number
871 has to be unsigned. */
873 if (unsigned_p || (n & high_bit))
875 putithere->typed_val_int.type = unsigned_type;
879 putithere->typed_val_int.type = signed_type;
889 enum exp_opcode opcode;
892 static const struct token tokentab3[] =
894 {"shr", RSH, BINOP_END},
895 {"shl", LSH, BINOP_END},
896 {"and", ANDAND, BINOP_END},
897 {"div", DIV, BINOP_END},
898 {"not", NOT, BINOP_END},
899 {"mod", MOD, BINOP_END},
900 {"inc", INCREMENT, BINOP_END},
901 {"dec", DECREMENT, BINOP_END},
902 {"xor", XOR, BINOP_END}
905 static const struct token tokentab2[] =
907 {"or", OR, BINOP_END},
908 {"<>", NOTEQUAL, BINOP_END},
909 {"<=", LEQ, BINOP_END},
910 {">=", GEQ, BINOP_END},
911 {":=", ASSIGN, BINOP_END}
914 /* Allocate uppercased var */
915 /* make an uppercased copy of tokstart */
916 static char * uptok (tokstart, namelen)
921 char *uptokstart = (char *)malloc(namelen+1);
922 for (i = 0;i <= namelen;i++)
924 if ((tokstart[i]>='a' && tokstart[i]<='z'))
925 uptokstart[i] = tokstart[i]-('a'-'A');
927 uptokstart[i] = tokstart[i];
929 uptokstart[namelen]='\0';
932 /* Read one token, getting characters through lexptr. */
946 static char *tempbuf;
947 static int tempbufsize;
952 /* See if it is a special token of length 3. */
953 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
954 if (STREQN (tokstart, tokentab3[i].operator, 3))
957 yylval.opcode = tokentab3[i].opcode;
958 return tokentab3[i].token;
961 /* See if it is a special token of length 2. */
962 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
963 if (STREQN (tokstart, tokentab2[i].operator, 2))
966 yylval.opcode = tokentab2[i].opcode;
967 return tokentab2[i].token;
970 switch (c = *tokstart)
982 /* We either have a character constant ('0' or '\177' for example)
983 or we have a quoted symbol reference ('foo(int,int)' in object pascal
988 c = parse_escape (&lexptr);
990 error ("Empty character constant.");
992 yylval.typed_val_int.val = c;
993 yylval.typed_val_int.type = builtin_type_char;
998 namelen = skip_quoted (tokstart) - tokstart;
1001 lexptr = tokstart + namelen;
1002 if (lexptr[-1] != '\'')
1003 error ("Unmatched single quote.");
1006 uptokstart = uptok(tokstart,namelen);
1009 error ("Invalid character constant.");
1019 if (paren_depth == 0)
1026 if (comma_terminates && paren_depth == 0)
1032 /* Might be a floating point number. */
1033 if (lexptr[1] < '0' || lexptr[1] > '9')
1034 goto symbol; /* Nope, must be a symbol. */
1035 /* FALL THRU into number case. */
1048 /* It's a number. */
1049 int got_dot = 0, got_e = 0, toktype;
1050 register char *p = tokstart;
1051 int hex = input_radix > 10;
1053 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1058 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1066 /* This test includes !hex because 'e' is a valid hex digit
1067 and thus does not indicate a floating point number when
1068 the radix is hex. */
1069 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1070 got_dot = got_e = 1;
1071 /* This test does not include !hex, because a '.' always indicates
1072 a decimal floating point number regardless of the radix. */
1073 else if (!got_dot && *p == '.')
1075 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1076 && (*p == '-' || *p == '+'))
1077 /* This is the sign of the exponent, not the end of the
1080 /* We will take any letters or digits. parse_number will
1081 complain if past the radix, or if L or U are not final. */
1082 else if ((*p < '0' || *p > '9')
1083 && ((*p < 'a' || *p > 'z')
1084 && (*p < 'A' || *p > 'Z')))
1087 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1088 if (toktype == ERROR)
1090 char *err_copy = (char *) alloca (p - tokstart + 1);
1092 memcpy (err_copy, tokstart, p - tokstart);
1093 err_copy[p - tokstart] = 0;
1094 error ("Invalid number \"%s\".", err_copy);
1125 /* Build the gdb internal form of the input string in tempbuf,
1126 translating any standard C escape forms seen. Note that the
1127 buffer is null byte terminated *only* for the convenience of
1128 debugging gdb itself and printing the buffer contents when
1129 the buffer contains no embedded nulls. Gdb does not depend
1130 upon the buffer being null byte terminated, it uses the length
1131 string instead. This allows gdb to handle C strings (as well
1132 as strings in other languages) with embedded null bytes */
1134 tokptr = ++tokstart;
1138 /* Grow the static temp buffer if necessary, including allocating
1139 the first one on demand. */
1140 if (tempbufindex + 1 >= tempbufsize)
1142 tempbuf = (char *) realloc (tempbuf, tempbufsize += 64);
1148 /* Do nothing, loop will terminate. */
1152 c = parse_escape (&tokptr);
1157 tempbuf[tempbufindex++] = c;
1160 tempbuf[tempbufindex++] = *tokptr++;
1163 } while ((*tokptr != '"') && (*tokptr != '\0'));
1164 if (*tokptr++ != '"')
1166 error ("Unterminated string in expression.");
1168 tempbuf[tempbufindex] = '\0'; /* See note above */
1169 yylval.sval.ptr = tempbuf;
1170 yylval.sval.length = tempbufindex;
1175 if (!(c == '_' || c == '$'
1176 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1177 /* We must have come across a bad character (e.g. ';'). */
1178 error ("Invalid character '%c' in expression.", c);
1180 /* It's a name. See how long it is. */
1182 for (c = tokstart[namelen];
1183 (c == '_' || c == '$' || (c >= '0' && c <= '9')
1184 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
1186 /* Template parameter lists are part of the name.
1187 FIXME: This mishandles `print $a<4&&$a>3'. */
1191 int nesting_level = 1;
1192 while (tokstart[++i])
1194 if (tokstart[i] == '<')
1196 else if (tokstart[i] == '>')
1198 if (--nesting_level == 0)
1202 if (tokstart[i] == '>')
1208 /* do NOT uppercase internals because of registers !!! */
1209 c = tokstart[++namelen];
1212 uptokstart = uptok(tokstart,namelen);
1214 /* The token "if" terminates the expression and is NOT
1215 removed from the input stream. */
1216 if (namelen == 2 && uptokstart[0] == 'I' && uptokstart[1] == 'F')
1225 /* Catch specific keywords. Should be done with a data structure. */
1229 if (STREQ (uptokstart, "OBJECT"))
1231 if (STREQ (uptokstart, "RECORD"))
1233 if (STREQ (uptokstart, "SIZEOF"))
1237 if (STREQ (uptokstart, "CLASS"))
1239 if (STREQ (uptokstart, "FALSE"))
1246 if (STREQ (uptokstart, "TRUE"))
1251 if (STREQ (uptokstart, "SELF"))
1253 /* here we search for 'this' like
1254 inserted in FPC stabs debug info */
1255 static const char this_name[] =
1256 { /* CPLUS_MARKER,*/ 't', 'h', 'i', 's', '\0' };
1258 if (lookup_symbol (this_name, expression_context_block,
1259 VAR_NAMESPACE, (int *) NULL,
1260 (struct symtab **) NULL))
1268 yylval.sval.ptr = tokstart;
1269 yylval.sval.length = namelen;
1271 if (*tokstart == '$')
1273 /* $ is the normal prefix for pascal hexadecimal values
1274 but this conflicts with the GDB use for debugger variables
1275 so in expression to enter hexadecimal values
1276 we still need to use C syntax with 0xff */
1277 write_dollar_variable (yylval.sval);
1281 /* Use token-type BLOCKNAME for symbols that happen to be defined as
1282 functions or symtabs. If this is not so, then ...
1283 Use token-type TYPENAME for symbols that happen to be defined
1284 currently as names of types; NAME for other symbols.
1285 The caller is not constrained to care about the distinction. */
1287 char *tmp = copy_name (yylval.sval);
1289 int is_a_field_of_this = 0;
1292 sym = lookup_symbol (tmp, expression_context_block,
1294 &is_a_field_of_this,
1295 (struct symtab **) NULL);
1296 /* second chance uppercased ! */
1299 for (i = 0;i <= namelen;i++)
1301 if ((tmp[i]>='a' && tmp[i]<='z'))
1302 tmp[i] -= ('a'-'A');
1303 /* I am not sure that copy_name gives excatly the same result ! */
1304 if ((tokstart[i]>='a' && tokstart[i]<='z'))
1305 tokstart[i] -= ('a'-'A');
1307 sym = lookup_symbol (tmp, expression_context_block,
1309 &is_a_field_of_this,
1310 (struct symtab **) NULL);
1312 /* Call lookup_symtab, not lookup_partial_symtab, in case there are
1313 no psymtabs (coff, xcoff, or some future change to blow away the
1314 psymtabs once once symbols are read). */
1315 if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1316 lookup_symtab (tmp))
1318 yylval.ssym.sym = sym;
1319 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1322 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1325 /* Despite the following flaw, we need to keep this code enabled.
1326 Because we can get called from check_stub_method, if we don't
1327 handle nested types then it screws many operations in any
1328 program which uses nested types. */
1329 /* In "A::x", if x is a member function of A and there happens
1330 to be a type (nested or not, since the stabs don't make that
1331 distinction) named x, then this code incorrectly thinks we
1332 are dealing with nested types rather than a member function. */
1336 struct symbol *best_sym;
1338 /* Look ahead to detect nested types. This probably should be
1339 done in the grammar, but trying seemed to introduce a lot
1340 of shift/reduce and reduce/reduce conflicts. It's possible
1341 that it could be done, though. Or perhaps a non-grammar, but
1342 less ad hoc, approach would work well. */
1344 /* Since we do not currently have any way of distinguishing
1345 a nested type from a non-nested one (the stabs don't tell
1346 us whether a type is nested), we just ignore the
1353 /* Skip whitespace. */
1354 while (*p == ' ' || *p == '\t' || *p == '\n')
1356 if (*p == ':' && p[1] == ':')
1358 /* Skip the `::'. */
1360 /* Skip whitespace. */
1361 while (*p == ' ' || *p == '\t' || *p == '\n')
1364 while (*p == '_' || *p == '$' || (*p >= '0' && *p <= '9')
1365 || (*p >= 'a' && *p <= 'z')
1366 || (*p >= 'A' && *p <= 'Z'))
1370 struct symbol *cur_sym;
1371 /* As big as the whole rest of the expression, which is
1372 at least big enough. */
1373 char *ncopy = alloca (strlen (tmp)+strlen (namestart)+3);
1377 memcpy (tmp1, tmp, strlen (tmp));
1378 tmp1 += strlen (tmp);
1379 memcpy (tmp1, "::", 2);
1381 memcpy (tmp1, namestart, p - namestart);
1382 tmp1[p - namestart] = '\0';
1383 cur_sym = lookup_symbol (ncopy, expression_context_block,
1384 VAR_NAMESPACE, (int *) NULL,
1385 (struct symtab **) NULL);
1388 if (SYMBOL_CLASS (cur_sym) == LOC_TYPEDEF)
1406 yylval.tsym.type = SYMBOL_TYPE (best_sym);
1408 yylval.tsym.type = SYMBOL_TYPE (sym);
1412 if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1415 /* Input names that aren't symbols but ARE valid hex numbers,
1416 when the input radix permits them, can be names or numbers
1417 depending on the parse. Note we support radixes > 16 here. */
1419 ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1420 (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1422 YYSTYPE newlval; /* Its value is ignored. */
1423 hextype = parse_number (tokstart, namelen, 0, &newlval);
1426 yylval.ssym.sym = sym;
1427 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1433 /* Any other kind of symbol */
1434 yylval.ssym.sym = sym;
1435 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1444 error ("A %s in expression, near `%s'.", (msg ? msg : "error"), lexptr);