1 /* YACC parser for C expressions, for GDB.
2 Copyright (C) 1986, 1989-2000, 2003-2004, 2006-2012 Free Software
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 3 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, see <http://www.gnu.org/licenses/>. */
20 /* Parse a C expression from text in a string,
21 and return the result as a struct expression pointer.
22 That structure contains arithmetic operations in reverse polish,
23 with constants represented by operations that are followed by special data.
24 See expression.h for the details of the format.
25 What is important here is that it can be built up sequentially
26 during the process of parsing; the lower levels of the tree always
27 come first in the result.
29 Note that malloc's and realloc's in this file are transformed to
30 xmalloc and xrealloc respectively by the same sed command in the
31 makefile that remaps any other malloc/realloc inserted by the parser
32 generator. Doing this with #defines and trying to control the interaction
33 with include files (<malloc.h> and <stdlib.h> for example) just became
34 too messy, particularly when such includes can be inserted at random
35 times by the parser generator. */
40 #include "gdb_string.h"
42 #include "expression.h"
44 #include "parser-defs.h"
47 #include "bfd.h" /* Required by objfiles.h. */
48 #include "symfile.h" /* Required by objfiles.h. */
49 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
52 #include "cp-support.h"
54 #include "gdb_assert.h"
55 #include "macroscope.h"
57 #define parse_type builtin_type (parse_gdbarch)
59 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
60 as well as gratuitiously global symbol names, so we can have multiple
61 yacc generated parsers in gdb. Note that these are only the variables
62 produced by yacc. If other parser generators (bison, byacc, etc) produce
63 additional global names that conflict at link time, then those parser
64 generators need to be fixed instead of adding those names to this list. */
66 #define yymaxdepth c_maxdepth
67 #define yyparse c_parse_internal
69 #define yyerror c_error
72 #define yydebug c_debug
81 #define yyerrflag c_errflag
82 #define yynerrs c_nerrs
87 #define yystate c_state
93 #define yyreds c_reds /* With YYDEBUG defined */
94 #define yytoks c_toks /* With YYDEBUG defined */
95 #define yyname c_name /* With YYDEBUG defined */
96 #define yyrule c_rule /* With YYDEBUG defined */
99 #define yydefred c_yydefred
100 #define yydgoto c_yydgoto
101 #define yysindex c_yysindex
102 #define yyrindex c_yyrindex
103 #define yygindex c_yygindex
104 #define yytable c_yytable
105 #define yycheck c_yycheck
107 #define yysslim c_yysslim
108 #define yyssp c_yyssp
109 #define yystacksize c_yystacksize
111 #define yyvsp c_yyvsp
114 #define YYDEBUG 1 /* Default to yydebug support */
117 #define YYFPRINTF parser_fprintf
121 static int yylex (void);
123 void yyerror (char *);
127 /* Although the yacc "value" of an expression is not used,
128 since the result is stored in the structure being created,
129 other node types do have values. */
145 } typed_val_decfloat;
149 struct typed_stoken tsval;
151 struct symtoken ssym;
154 enum exp_opcode opcode;
155 struct internalvar *ivar;
157 struct stoken_vector svec;
163 /* YYSTYPE gets defined by %union */
164 static int parse_number (char *, int, int, YYSTYPE *);
165 static struct stoken operator_stoken (const char *);
168 %type <voidval> exp exp1 type_exp start variable qualified_name lcurly
170 %type <tval> type typebase
171 %type <tvec> nonempty_typelist
172 /* %type <bval> block */
174 /* Fancy type parsing. */
176 %type <lval> array_mod
177 %type <tval> conversion_type_id
179 %token <typed_val_int> INT
180 %token <typed_val_float> FLOAT
181 %token <typed_val_decfloat> DECFLOAT
183 /* Both NAME and TYPENAME tokens represent symbols in the input,
184 and both convey their data as strings.
185 But a TYPENAME is a string that happens to be defined as a typedef
186 or builtin type name (such as int or char)
187 and a NAME is any other symbol.
188 Contexts where this distinction is not important can use the
189 nonterminal "name", which matches either NAME or TYPENAME. */
191 %token <tsval> STRING
193 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
194 %token <ssym> UNKNOWN_CPP_NAME
195 %token <voidval> COMPLETE
196 %token <tsym> TYPENAME
198 %type <svec> string_exp
199 %type <ssym> name_not_typename
200 %type <tsym> typename
202 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
203 but which would parse as a valid number in the current input radix.
204 E.g. "c" when input_radix==16. Depending on the parse, it will be
205 turned into a name or into a number. */
207 %token <ssym> NAME_OR_INT
210 %token STRUCT CLASS UNION ENUM SIZEOF UNSIGNED COLONCOLON
214 %type <sval> operator
215 %token REINTERPRET_CAST DYNAMIC_CAST STATIC_CAST CONST_CAST
218 /* Special type cases, put in to allow the parser to distinguish different
220 %token SIGNED_KEYWORD LONG SHORT INT_KEYWORD CONST_KEYWORD VOLATILE_KEYWORD DOUBLE_KEYWORD
222 %token <sval> VARIABLE
224 %token <opcode> ASSIGN_MODIFY
233 %right '=' ASSIGN_MODIFY
241 %left '<' '>' LEQ GEQ
246 %right UNARY INCREMENT DECREMENT
247 %right ARROW ARROW_STAR '.' DOT_STAR '[' '('
248 %token <ssym> BLOCKNAME
249 %token <bval> FILENAME
261 { write_exp_elt_opcode(OP_TYPE);
262 write_exp_elt_type($1);
263 write_exp_elt_opcode(OP_TYPE);}
266 /* Expressions, including the comma operator. */
269 { write_exp_elt_opcode (BINOP_COMMA); }
272 /* Expressions, not including the comma operator. */
273 exp : '*' exp %prec UNARY
274 { write_exp_elt_opcode (UNOP_IND); }
277 exp : '&' exp %prec UNARY
278 { write_exp_elt_opcode (UNOP_ADDR); }
281 exp : '-' exp %prec UNARY
282 { write_exp_elt_opcode (UNOP_NEG); }
285 exp : '+' exp %prec UNARY
286 { write_exp_elt_opcode (UNOP_PLUS); }
289 exp : '!' exp %prec UNARY
290 { write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
293 exp : '~' exp %prec UNARY
294 { write_exp_elt_opcode (UNOP_COMPLEMENT); }
297 exp : INCREMENT exp %prec UNARY
298 { write_exp_elt_opcode (UNOP_PREINCREMENT); }
301 exp : DECREMENT exp %prec UNARY
302 { write_exp_elt_opcode (UNOP_PREDECREMENT); }
305 exp : exp INCREMENT %prec UNARY
306 { write_exp_elt_opcode (UNOP_POSTINCREMENT); }
309 exp : exp DECREMENT %prec UNARY
310 { write_exp_elt_opcode (UNOP_POSTDECREMENT); }
313 exp : SIZEOF exp %prec UNARY
314 { write_exp_elt_opcode (UNOP_SIZEOF); }
318 { write_exp_elt_opcode (STRUCTOP_PTR);
319 write_exp_string ($3);
320 write_exp_elt_opcode (STRUCTOP_PTR); }
323 exp : exp ARROW name COMPLETE
324 { mark_struct_expression ();
325 write_exp_elt_opcode (STRUCTOP_PTR);
326 write_exp_string ($3);
327 write_exp_elt_opcode (STRUCTOP_PTR); }
330 exp : exp ARROW COMPLETE
332 mark_struct_expression ();
333 write_exp_elt_opcode (STRUCTOP_PTR);
336 write_exp_string (s);
337 write_exp_elt_opcode (STRUCTOP_PTR); }
340 exp : exp ARROW qualified_name
341 { /* exp->type::name becomes exp->*(&type::name) */
342 /* Note: this doesn't work if name is a
343 static member! FIXME */
344 write_exp_elt_opcode (UNOP_ADDR);
345 write_exp_elt_opcode (STRUCTOP_MPTR); }
348 exp : exp ARROW_STAR exp
349 { write_exp_elt_opcode (STRUCTOP_MPTR); }
353 { write_exp_elt_opcode (STRUCTOP_STRUCT);
354 write_exp_string ($3);
355 write_exp_elt_opcode (STRUCTOP_STRUCT); }
358 exp : exp '.' name COMPLETE
359 { mark_struct_expression ();
360 write_exp_elt_opcode (STRUCTOP_STRUCT);
361 write_exp_string ($3);
362 write_exp_elt_opcode (STRUCTOP_STRUCT); }
365 exp : exp '.' COMPLETE
367 mark_struct_expression ();
368 write_exp_elt_opcode (STRUCTOP_STRUCT);
371 write_exp_string (s);
372 write_exp_elt_opcode (STRUCTOP_STRUCT); }
375 exp : exp '.' qualified_name
376 { /* exp.type::name becomes exp.*(&type::name) */
377 /* Note: this doesn't work if name is a
378 static member! FIXME */
379 write_exp_elt_opcode (UNOP_ADDR);
380 write_exp_elt_opcode (STRUCTOP_MEMBER); }
383 exp : exp DOT_STAR exp
384 { write_exp_elt_opcode (STRUCTOP_MEMBER); }
387 exp : exp '[' exp1 ']'
388 { write_exp_elt_opcode (BINOP_SUBSCRIPT); }
392 /* This is to save the value of arglist_len
393 being accumulated by an outer function call. */
394 { start_arglist (); }
395 arglist ')' %prec ARROW
396 { write_exp_elt_opcode (OP_FUNCALL);
397 write_exp_elt_longcst ((LONGEST) end_arglist ());
398 write_exp_elt_opcode (OP_FUNCALL); }
401 exp : UNKNOWN_CPP_NAME '('
403 /* This could potentially be a an argument defined
404 lookup function (Koenig). */
405 write_exp_elt_opcode (OP_ADL_FUNC);
406 write_exp_elt_block (expression_context_block);
407 write_exp_elt_sym (NULL); /* Placeholder. */
408 write_exp_string ($1.stoken);
409 write_exp_elt_opcode (OP_ADL_FUNC);
411 /* This is to save the value of arglist_len
412 being accumulated by an outer function call. */
416 arglist ')' %prec ARROW
418 write_exp_elt_opcode (OP_FUNCALL);
419 write_exp_elt_longcst ((LONGEST) end_arglist ());
420 write_exp_elt_opcode (OP_FUNCALL);
425 { start_arglist (); }
435 arglist : arglist ',' exp %prec ABOVE_COMMA
439 exp : exp '(' nonempty_typelist ')' const_or_volatile
441 write_exp_elt_opcode (TYPE_INSTANCE);
442 write_exp_elt_longcst ((LONGEST) $<ivec>3[0]);
443 for (i = 0; i < $<ivec>3[0]; ++i)
444 write_exp_elt_type ($<tvec>3[i + 1]);
445 write_exp_elt_longcst((LONGEST) $<ivec>3[0]);
446 write_exp_elt_opcode (TYPE_INSTANCE);
452 { $$ = end_arglist () - 1; }
454 exp : lcurly arglist rcurly %prec ARROW
455 { write_exp_elt_opcode (OP_ARRAY);
456 write_exp_elt_longcst ((LONGEST) 0);
457 write_exp_elt_longcst ((LONGEST) $3);
458 write_exp_elt_opcode (OP_ARRAY); }
461 exp : lcurly type rcurly exp %prec UNARY
462 { write_exp_elt_opcode (UNOP_MEMVAL);
463 write_exp_elt_type ($2);
464 write_exp_elt_opcode (UNOP_MEMVAL); }
467 exp : '(' type ')' exp %prec UNARY
468 { write_exp_elt_opcode (UNOP_CAST);
469 write_exp_elt_type ($2);
470 write_exp_elt_opcode (UNOP_CAST); }
477 /* Binary operators in order of decreasing precedence. */
480 { write_exp_elt_opcode (BINOP_REPEAT); }
484 { write_exp_elt_opcode (BINOP_MUL); }
488 { write_exp_elt_opcode (BINOP_DIV); }
492 { write_exp_elt_opcode (BINOP_REM); }
496 { write_exp_elt_opcode (BINOP_ADD); }
500 { write_exp_elt_opcode (BINOP_SUB); }
504 { write_exp_elt_opcode (BINOP_LSH); }
508 { write_exp_elt_opcode (BINOP_RSH); }
512 { write_exp_elt_opcode (BINOP_EQUAL); }
515 exp : exp NOTEQUAL exp
516 { write_exp_elt_opcode (BINOP_NOTEQUAL); }
520 { write_exp_elt_opcode (BINOP_LEQ); }
524 { write_exp_elt_opcode (BINOP_GEQ); }
528 { write_exp_elt_opcode (BINOP_LESS); }
532 { write_exp_elt_opcode (BINOP_GTR); }
536 { write_exp_elt_opcode (BINOP_BITWISE_AND); }
540 { write_exp_elt_opcode (BINOP_BITWISE_XOR); }
544 { write_exp_elt_opcode (BINOP_BITWISE_IOR); }
548 { write_exp_elt_opcode (BINOP_LOGICAL_AND); }
552 { write_exp_elt_opcode (BINOP_LOGICAL_OR); }
555 exp : exp '?' exp ':' exp %prec '?'
556 { write_exp_elt_opcode (TERNOP_COND); }
560 { write_exp_elt_opcode (BINOP_ASSIGN); }
563 exp : exp ASSIGN_MODIFY exp
564 { write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
565 write_exp_elt_opcode ($2);
566 write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
570 { write_exp_elt_opcode (OP_LONG);
571 write_exp_elt_type ($1.type);
572 write_exp_elt_longcst ((LONGEST)($1.val));
573 write_exp_elt_opcode (OP_LONG); }
578 struct stoken_vector vec;
581 write_exp_string_vector ($1.type, &vec);
587 parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
588 write_exp_elt_opcode (OP_LONG);
589 write_exp_elt_type (val.typed_val_int.type);
590 write_exp_elt_longcst ((LONGEST)val.typed_val_int.val);
591 write_exp_elt_opcode (OP_LONG);
597 { write_exp_elt_opcode (OP_DOUBLE);
598 write_exp_elt_type ($1.type);
599 write_exp_elt_dblcst ($1.dval);
600 write_exp_elt_opcode (OP_DOUBLE); }
604 { write_exp_elt_opcode (OP_DECFLOAT);
605 write_exp_elt_type ($1.type);
606 write_exp_elt_decfloatcst ($1.val);
607 write_exp_elt_opcode (OP_DECFLOAT); }
615 write_dollar_variable ($1);
619 exp : SIZEOF '(' type ')' %prec UNARY
620 { write_exp_elt_opcode (OP_LONG);
621 write_exp_elt_type (lookup_signed_typename
622 (parse_language, parse_gdbarch,
625 write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
626 write_exp_elt_opcode (OP_LONG); }
629 exp : REINTERPRET_CAST '<' type '>' '(' exp ')' %prec UNARY
630 { write_exp_elt_opcode (UNOP_REINTERPRET_CAST);
631 write_exp_elt_type ($3);
632 write_exp_elt_opcode (UNOP_REINTERPRET_CAST); }
635 exp : STATIC_CAST '<' type '>' '(' exp ')' %prec UNARY
636 { write_exp_elt_opcode (UNOP_CAST);
637 write_exp_elt_type ($3);
638 write_exp_elt_opcode (UNOP_CAST); }
641 exp : DYNAMIC_CAST '<' type '>' '(' exp ')' %prec UNARY
642 { write_exp_elt_opcode (UNOP_DYNAMIC_CAST);
643 write_exp_elt_type ($3);
644 write_exp_elt_opcode (UNOP_DYNAMIC_CAST); }
647 exp : CONST_CAST '<' type '>' '(' exp ')' %prec UNARY
648 { /* We could do more error checking here, but
649 it doesn't seem worthwhile. */
650 write_exp_elt_opcode (UNOP_CAST);
651 write_exp_elt_type ($3);
652 write_exp_elt_opcode (UNOP_CAST); }
658 /* We copy the string here, and not in the
659 lexer, to guarantee that we do not leak a
660 string. Note that we follow the
661 NUL-termination convention of the
663 struct typed_stoken *vec = XNEW (struct typed_stoken);
668 vec->length = $1.length;
669 vec->ptr = malloc ($1.length + 1);
670 memcpy (vec->ptr, $1.ptr, $1.length + 1);
675 /* Note that we NUL-terminate here, but just
679 $$.tokens = realloc ($$.tokens,
680 $$.len * sizeof (struct typed_stoken));
682 p = malloc ($2.length + 1);
683 memcpy (p, $2.ptr, $2.length + 1);
685 $$.tokens[$$.len - 1].type = $2.type;
686 $$.tokens[$$.len - 1].length = $2.length;
687 $$.tokens[$$.len - 1].ptr = p;
694 enum c_string_type type = C_STRING;
696 for (i = 0; i < $1.len; ++i)
698 switch ($1.tokens[i].type)
706 && type != $1.tokens[i].type)
707 error (_("Undefined string concatenation."));
708 type = $1.tokens[i].type;
712 internal_error (__FILE__, __LINE__,
713 "unrecognized type in string concatenation");
717 write_exp_string_vector (type, &$1);
718 for (i = 0; i < $1.len; ++i)
719 free ($1.tokens[i].ptr);
726 { write_exp_elt_opcode (OP_LONG);
727 write_exp_elt_type (parse_type->builtin_bool);
728 write_exp_elt_longcst ((LONGEST) 1);
729 write_exp_elt_opcode (OP_LONG); }
733 { write_exp_elt_opcode (OP_LONG);
734 write_exp_elt_type (parse_type->builtin_bool);
735 write_exp_elt_longcst ((LONGEST) 0);
736 write_exp_elt_opcode (OP_LONG); }
744 $$ = SYMBOL_BLOCK_VALUE ($1.sym);
746 error (_("No file or function \"%s\"."),
747 copy_name ($1.stoken));
755 block : block COLONCOLON name
757 = lookup_symbol (copy_name ($3), $1,
758 VAR_DOMAIN, (int *) NULL);
759 if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
760 error (_("No function \"%s\" in specified context."),
762 $$ = SYMBOL_BLOCK_VALUE (tem); }
765 variable: name_not_typename ENTRY
766 { struct symbol *sym = $1.sym;
768 if (sym == NULL || !SYMBOL_IS_ARGUMENT (sym)
769 || !symbol_read_needs_frame (sym))
770 error (_("@entry can be used only for function "
771 "parameters, not for \"%s\""),
772 copy_name ($1.stoken));
774 write_exp_elt_opcode (OP_VAR_ENTRY_VALUE);
775 write_exp_elt_sym (sym);
776 write_exp_elt_opcode (OP_VAR_ENTRY_VALUE);
780 variable: block COLONCOLON name
781 { struct symbol *sym;
782 sym = lookup_symbol (copy_name ($3), $1,
783 VAR_DOMAIN, (int *) NULL);
785 error (_("No symbol \"%s\" in specified context."),
787 if (symbol_read_needs_frame (sym))
789 if (innermost_block == 0
790 || contained_in (block_found,
792 innermost_block = block_found;
795 write_exp_elt_opcode (OP_VAR_VALUE);
796 /* block_found is set by lookup_symbol. */
797 write_exp_elt_block (block_found);
798 write_exp_elt_sym (sym);
799 write_exp_elt_opcode (OP_VAR_VALUE); }
802 qualified_name: TYPENAME COLONCOLON name
804 struct type *type = $1.type;
805 CHECK_TYPEDEF (type);
806 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
807 && TYPE_CODE (type) != TYPE_CODE_UNION
808 && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
809 error (_("`%s' is not defined as an aggregate type."),
812 write_exp_elt_opcode (OP_SCOPE);
813 write_exp_elt_type (type);
814 write_exp_string ($3);
815 write_exp_elt_opcode (OP_SCOPE);
817 | TYPENAME COLONCOLON '~' name
819 struct type *type = $1.type;
820 struct stoken tmp_token;
821 CHECK_TYPEDEF (type);
822 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
823 && TYPE_CODE (type) != TYPE_CODE_UNION
824 && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
825 error (_("`%s' is not defined as an aggregate type."),
828 tmp_token.ptr = (char*) alloca ($4.length + 2);
829 tmp_token.length = $4.length + 1;
830 tmp_token.ptr[0] = '~';
831 memcpy (tmp_token.ptr+1, $4.ptr, $4.length);
832 tmp_token.ptr[tmp_token.length] = 0;
834 /* Check for valid destructor name. */
835 destructor_name_p (tmp_token.ptr, $1.type);
836 write_exp_elt_opcode (OP_SCOPE);
837 write_exp_elt_type (type);
838 write_exp_string (tmp_token);
839 write_exp_elt_opcode (OP_SCOPE);
841 | TYPENAME COLONCOLON name COLONCOLON name
843 char *copy = copy_name ($3);
844 error (_("No type \"%s\" within class "
845 "or namespace \"%s\"."),
846 copy, TYPE_NAME ($1.type));
850 variable: qualified_name
851 | COLONCOLON name_not_typename
853 char *name = copy_name ($2.stoken);
855 struct minimal_symbol *msymbol;
858 lookup_symbol (name, (const struct block *) NULL,
859 VAR_DOMAIN, (int *) NULL);
862 write_exp_elt_opcode (OP_VAR_VALUE);
863 write_exp_elt_block (NULL);
864 write_exp_elt_sym (sym);
865 write_exp_elt_opcode (OP_VAR_VALUE);
869 msymbol = lookup_minimal_symbol (name, NULL, NULL);
871 write_exp_msymbol (msymbol);
872 else if (!have_full_symbols () && !have_partial_symbols ())
873 error (_("No symbol table is loaded. Use the \"file\" command."));
875 error (_("No symbol \"%s\" in current context."), name);
879 variable: name_not_typename
880 { struct symbol *sym = $1.sym;
884 if (symbol_read_needs_frame (sym))
886 if (innermost_block == 0
887 || contained_in (block_found,
889 innermost_block = block_found;
892 write_exp_elt_opcode (OP_VAR_VALUE);
893 /* We want to use the selected frame, not
894 another more inner frame which happens to
895 be in the same block. */
896 write_exp_elt_block (NULL);
897 write_exp_elt_sym (sym);
898 write_exp_elt_opcode (OP_VAR_VALUE);
900 else if ($1.is_a_field_of_this)
902 /* C++: it hangs off of `this'. Must
903 not inadvertently convert from a method call
905 if (innermost_block == 0
906 || contained_in (block_found,
908 innermost_block = block_found;
909 write_exp_elt_opcode (OP_THIS);
910 write_exp_elt_opcode (OP_THIS);
911 write_exp_elt_opcode (STRUCTOP_PTR);
912 write_exp_string ($1.stoken);
913 write_exp_elt_opcode (STRUCTOP_PTR);
917 struct minimal_symbol *msymbol;
918 char *arg = copy_name ($1.stoken);
921 lookup_minimal_symbol (arg, NULL, NULL);
923 write_exp_msymbol (msymbol);
924 else if (!have_full_symbols () && !have_partial_symbols ())
925 error (_("No symbol table is loaded. Use the \"file\" command."));
927 error (_("No symbol \"%s\" in current context."),
928 copy_name ($1.stoken));
933 space_identifier : '@' NAME
934 { insert_type_address_space (copy_name ($2.stoken)); }
937 const_or_volatile: const_or_volatile_noopt
941 cv_with_space_id : const_or_volatile space_identifier const_or_volatile
944 const_or_volatile_or_space_identifier_noopt: cv_with_space_id
945 | const_or_volatile_noopt
948 const_or_volatile_or_space_identifier:
949 const_or_volatile_or_space_identifier_noopt
955 { insert_type (tp_pointer); }
956 const_or_volatile_or_space_identifier
958 { insert_type (tp_pointer); }
959 const_or_volatile_or_space_identifier
961 { insert_type (tp_reference); }
963 { insert_type (tp_reference); }
966 abs_decl: ptr_operator direct_abs_decl
971 direct_abs_decl: '(' abs_decl ')'
972 | direct_abs_decl array_mod
975 push_type (tp_array);
980 push_type (tp_array);
983 | direct_abs_decl func_mod
984 { push_type (tp_function); }
986 { push_type (tp_function); }
996 | '(' nonempty_typelist ')'
1000 /* We used to try to recognize pointer to member types here, but
1001 that didn't work (shift/reduce conflicts meant that these rules never
1002 got executed). The problem is that
1003 int (foo::bar::baz::bizzle)
1004 is a function type but
1005 int (foo::bar::baz::bizzle::*)
1006 is a pointer to member type. Stroustrup loses again! */
1011 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
1015 { $$ = lookup_signed_typename (parse_language,
1019 { $$ = lookup_signed_typename (parse_language,
1023 { $$ = lookup_signed_typename (parse_language,
1027 { $$ = lookup_signed_typename (parse_language,
1030 | LONG SIGNED_KEYWORD INT_KEYWORD
1031 { $$ = lookup_signed_typename (parse_language,
1034 | LONG SIGNED_KEYWORD
1035 { $$ = lookup_signed_typename (parse_language,
1038 | SIGNED_KEYWORD LONG INT_KEYWORD
1039 { $$ = lookup_signed_typename (parse_language,
1042 | UNSIGNED LONG INT_KEYWORD
1043 { $$ = lookup_unsigned_typename (parse_language,
1046 | LONG UNSIGNED INT_KEYWORD
1047 { $$ = lookup_unsigned_typename (parse_language,
1051 { $$ = lookup_unsigned_typename (parse_language,
1055 { $$ = lookup_signed_typename (parse_language,
1058 | LONG LONG INT_KEYWORD
1059 { $$ = lookup_signed_typename (parse_language,
1062 | LONG LONG SIGNED_KEYWORD INT_KEYWORD
1063 { $$ = lookup_signed_typename (parse_language,
1066 | LONG LONG SIGNED_KEYWORD
1067 { $$ = lookup_signed_typename (parse_language,
1070 | SIGNED_KEYWORD LONG LONG
1071 { $$ = lookup_signed_typename (parse_language,
1074 | SIGNED_KEYWORD LONG LONG INT_KEYWORD
1075 { $$ = lookup_signed_typename (parse_language,
1078 | UNSIGNED LONG LONG
1079 { $$ = lookup_unsigned_typename (parse_language,
1082 | UNSIGNED LONG LONG INT_KEYWORD
1083 { $$ = lookup_unsigned_typename (parse_language,
1086 | LONG LONG UNSIGNED
1087 { $$ = lookup_unsigned_typename (parse_language,
1090 | LONG LONG UNSIGNED INT_KEYWORD
1091 { $$ = lookup_unsigned_typename (parse_language,
1095 { $$ = lookup_signed_typename (parse_language,
1098 | SHORT SIGNED_KEYWORD INT_KEYWORD
1099 { $$ = lookup_signed_typename (parse_language,
1102 | SHORT SIGNED_KEYWORD
1103 { $$ = lookup_signed_typename (parse_language,
1106 | UNSIGNED SHORT INT_KEYWORD
1107 { $$ = lookup_unsigned_typename (parse_language,
1111 { $$ = lookup_unsigned_typename (parse_language,
1114 | SHORT UNSIGNED INT_KEYWORD
1115 { $$ = lookup_unsigned_typename (parse_language,
1119 { $$ = lookup_typename (parse_language, parse_gdbarch,
1120 "double", (struct block *) NULL,
1122 | LONG DOUBLE_KEYWORD
1123 { $$ = lookup_typename (parse_language, parse_gdbarch,
1125 (struct block *) NULL, 0); }
1127 { $$ = lookup_struct (copy_name ($2),
1128 expression_context_block); }
1130 { $$ = lookup_struct (copy_name ($2),
1131 expression_context_block); }
1133 { $$ = lookup_union (copy_name ($2),
1134 expression_context_block); }
1136 { $$ = lookup_enum (copy_name ($2),
1137 expression_context_block); }
1139 { $$ = lookup_unsigned_typename (parse_language,
1141 TYPE_NAME($2.type)); }
1143 { $$ = lookup_unsigned_typename (parse_language,
1146 | SIGNED_KEYWORD typename
1147 { $$ = lookup_signed_typename (parse_language,
1149 TYPE_NAME($2.type)); }
1151 { $$ = lookup_signed_typename (parse_language,
1154 /* It appears that this rule for templates is never
1155 reduced; template recognition happens by lookahead
1156 in the token processing code in yylex. */
1157 | TEMPLATE name '<' type '>'
1158 { $$ = lookup_template_type(copy_name($2), $4,
1159 expression_context_block);
1161 | const_or_volatile_or_space_identifier_noopt typebase
1162 { $$ = follow_types ($2); }
1163 | typebase const_or_volatile_or_space_identifier_noopt
1164 { $$ = follow_types ($1); }
1170 $$.stoken.ptr = "int";
1171 $$.stoken.length = 3;
1172 $$.type = lookup_signed_typename (parse_language,
1178 $$.stoken.ptr = "long";
1179 $$.stoken.length = 4;
1180 $$.type = lookup_signed_typename (parse_language,
1186 $$.stoken.ptr = "short";
1187 $$.stoken.length = 5;
1188 $$.type = lookup_signed_typename (parse_language,
1196 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
1197 $<ivec>$[0] = 1; /* Number of types in vector */
1200 | nonempty_typelist ',' type
1201 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
1202 $$ = (struct type **) realloc ((char *) $1, len);
1203 $$[$<ivec>$[0]] = $3;
1209 { $$ = follow_types ($1); }
1212 conversion_type_id: typebase conversion_declarator
1213 { $$ = follow_types ($1); }
1216 conversion_declarator: /* Nothing. */
1217 | ptr_operator conversion_declarator
1220 const_and_volatile: CONST_KEYWORD VOLATILE_KEYWORD
1221 | VOLATILE_KEYWORD CONST_KEYWORD
1224 const_or_volatile_noopt: const_and_volatile
1225 { insert_type (tp_const);
1226 insert_type (tp_volatile);
1229 { insert_type (tp_const); }
1231 { insert_type (tp_volatile); }
1234 operator: OPERATOR NEW
1235 { $$ = operator_stoken (" new"); }
1237 { $$ = operator_stoken (" delete"); }
1238 | OPERATOR NEW '[' ']'
1239 { $$ = operator_stoken (" new[]"); }
1240 | OPERATOR DELETE '[' ']'
1241 { $$ = operator_stoken (" delete[]"); }
1243 { $$ = operator_stoken ("+"); }
1245 { $$ = operator_stoken ("-"); }
1247 { $$ = operator_stoken ("*"); }
1249 { $$ = operator_stoken ("/"); }
1251 { $$ = operator_stoken ("%"); }
1253 { $$ = operator_stoken ("^"); }
1255 { $$ = operator_stoken ("&"); }
1257 { $$ = operator_stoken ("|"); }
1259 { $$ = operator_stoken ("~"); }
1261 { $$ = operator_stoken ("!"); }
1263 { $$ = operator_stoken ("="); }
1265 { $$ = operator_stoken ("<"); }
1267 { $$ = operator_stoken (">"); }
1268 | OPERATOR ASSIGN_MODIFY
1269 { const char *op = "unknown";
1293 case BINOP_BITWISE_IOR:
1296 case BINOP_BITWISE_AND:
1299 case BINOP_BITWISE_XOR:
1306 $$ = operator_stoken (op);
1309 { $$ = operator_stoken ("<<"); }
1311 { $$ = operator_stoken (">>"); }
1313 { $$ = operator_stoken ("=="); }
1315 { $$ = operator_stoken ("!="); }
1317 { $$ = operator_stoken ("<="); }
1319 { $$ = operator_stoken (">="); }
1321 { $$ = operator_stoken ("&&"); }
1323 { $$ = operator_stoken ("||"); }
1324 | OPERATOR INCREMENT
1325 { $$ = operator_stoken ("++"); }
1326 | OPERATOR DECREMENT
1327 { $$ = operator_stoken ("--"); }
1329 { $$ = operator_stoken (","); }
1330 | OPERATOR ARROW_STAR
1331 { $$ = operator_stoken ("->*"); }
1333 { $$ = operator_stoken ("->"); }
1335 { $$ = operator_stoken ("()"); }
1337 { $$ = operator_stoken ("[]"); }
1338 | OPERATOR conversion_type_id
1341 struct ui_file *buf = mem_fileopen ();
1343 c_print_type ($2, NULL, buf, -1, 0);
1344 name = ui_file_xstrdup (buf, &length);
1345 ui_file_delete (buf);
1346 $$ = operator_stoken (name);
1353 name : NAME { $$ = $1.stoken; }
1354 | BLOCKNAME { $$ = $1.stoken; }
1355 | TYPENAME { $$ = $1.stoken; }
1356 | NAME_OR_INT { $$ = $1.stoken; }
1357 | UNKNOWN_CPP_NAME { $$ = $1.stoken; }
1358 | operator { $$ = $1; }
1361 name_not_typename : NAME
1363 /* These would be useful if name_not_typename was useful, but it is just
1364 a fake for "variable", so these cause reduce/reduce conflicts because
1365 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
1366 =exp) or just an exp. If name_not_typename was ever used in an lvalue
1367 context where only a name could occur, this might be useful.
1373 $$.sym = lookup_symbol ($1.ptr,
1374 expression_context_block,
1376 &$$.is_a_field_of_this);
1383 /* Returns a stoken of the operator name given by OP (which does not
1384 include the string "operator"). */
1385 static struct stoken
1386 operator_stoken (const char *op)
1388 static const char *operator_string = "operator";
1389 struct stoken st = { NULL, 0 };
1390 st.length = strlen (operator_string) + strlen (op);
1391 st.ptr = malloc (st.length + 1);
1392 strcpy (st.ptr, operator_string);
1393 strcat (st.ptr, op);
1395 /* The toplevel (c_parse) will free the memory allocated here. */
1396 make_cleanup (free, st.ptr);
1400 /* Take care of parsing a number (anything that starts with a digit).
1401 Set yylval and return the token type; update lexptr.
1402 LEN is the number of characters in it. */
1404 /*** Needs some error checking for the float case ***/
1407 parse_number (char *p, int len, int parsed_float, YYSTYPE *putithere)
1409 /* FIXME: Shouldn't these be unsigned? We don't deal with negative values
1410 here, and we do kind of silly things like cast to unsigned. */
1417 int base = input_radix;
1420 /* Number of "L" suffixes encountered. */
1423 /* We have found a "L" or "U" suffix. */
1424 int found_suffix = 0;
1427 struct type *signed_type;
1428 struct type *unsigned_type;
1432 /* If it ends at "df", "dd" or "dl", take it as type of decimal floating
1433 point. Return DECFLOAT. */
1435 if (len >= 2 && p[len - 2] == 'd' && p[len - 1] == 'f')
1438 putithere->typed_val_decfloat.type
1439 = parse_type->builtin_decfloat;
1440 decimal_from_string (putithere->typed_val_decfloat.val, 4,
1441 gdbarch_byte_order (parse_gdbarch), p);
1446 if (len >= 2 && p[len - 2] == 'd' && p[len - 1] == 'd')
1449 putithere->typed_val_decfloat.type
1450 = parse_type->builtin_decdouble;
1451 decimal_from_string (putithere->typed_val_decfloat.val, 8,
1452 gdbarch_byte_order (parse_gdbarch), p);
1457 if (len >= 2 && p[len - 2] == 'd' && p[len - 1] == 'l')
1460 putithere->typed_val_decfloat.type
1461 = parse_type->builtin_declong;
1462 decimal_from_string (putithere->typed_val_decfloat.val, 16,
1463 gdbarch_byte_order (parse_gdbarch), p);
1468 if (! parse_c_float (parse_gdbarch, p, len,
1469 &putithere->typed_val_float.dval,
1470 &putithere->typed_val_float.type))
1475 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
1519 if (c >= 'A' && c <= 'Z')
1521 if (c != 'l' && c != 'u')
1523 if (c >= '0' && c <= '9')
1531 if (base > 10 && c >= 'a' && c <= 'f')
1535 n += i = c - 'a' + 10;
1548 return ERROR; /* Char not a digit */
1551 return ERROR; /* Invalid digit in this base */
1553 /* Portably test for overflow (only works for nonzero values, so make
1554 a second check for zero). FIXME: Can't we just make n and prevn
1555 unsigned and avoid this? */
1556 if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
1557 unsigned_p = 1; /* Try something unsigned */
1559 /* Portably test for unsigned overflow.
1560 FIXME: This check is wrong; for example it doesn't find overflow
1561 on 0x123456789 when LONGEST is 32 bits. */
1562 if (c != 'l' && c != 'u' && n != 0)
1564 if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
1565 error (_("Numeric constant too large."));
1570 /* An integer constant is an int, a long, or a long long. An L
1571 suffix forces it to be long; an LL suffix forces it to be long
1572 long. If not forced to a larger size, it gets the first type of
1573 the above that it fits in. To figure out whether it fits, we
1574 shift it right and see whether anything remains. Note that we
1575 can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
1576 operation, because many compilers will warn about such a shift
1577 (which always produces a zero result). Sometimes gdbarch_int_bit
1578 or gdbarch_long_bit will be that big, sometimes not. To deal with
1579 the case where it is we just always shift the value more than
1580 once, with fewer bits each time. */
1582 un = (ULONGEST)n >> 2;
1584 && (un >> (gdbarch_int_bit (parse_gdbarch) - 2)) == 0)
1586 high_bit = ((ULONGEST)1) << (gdbarch_int_bit (parse_gdbarch) - 1);
1588 /* A large decimal (not hex or octal) constant (between INT_MAX
1589 and UINT_MAX) is a long or unsigned long, according to ANSI,
1590 never an unsigned int, but this code treats it as unsigned
1591 int. This probably should be fixed. GCC gives a warning on
1594 unsigned_type = parse_type->builtin_unsigned_int;
1595 signed_type = parse_type->builtin_int;
1597 else if (long_p <= 1
1598 && (un >> (gdbarch_long_bit (parse_gdbarch) - 2)) == 0)
1600 high_bit = ((ULONGEST)1) << (gdbarch_long_bit (parse_gdbarch) - 1);
1601 unsigned_type = parse_type->builtin_unsigned_long;
1602 signed_type = parse_type->builtin_long;
1607 if (sizeof (ULONGEST) * HOST_CHAR_BIT
1608 < gdbarch_long_long_bit (parse_gdbarch))
1609 /* A long long does not fit in a LONGEST. */
1610 shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
1612 shift = (gdbarch_long_long_bit (parse_gdbarch) - 1);
1613 high_bit = (ULONGEST) 1 << shift;
1614 unsigned_type = parse_type->builtin_unsigned_long_long;
1615 signed_type = parse_type->builtin_long_long;
1618 putithere->typed_val_int.val = n;
1620 /* If the high bit of the worked out type is set then this number
1621 has to be unsigned. */
1623 if (unsigned_p || (n & high_bit))
1625 putithere->typed_val_int.type = unsigned_type;
1629 putithere->typed_val_int.type = signed_type;
1635 /* Temporary obstack used for holding strings. */
1636 static struct obstack tempbuf;
1637 static int tempbuf_init;
1639 /* Parse a C escape sequence. The initial backslash of the sequence
1640 is at (*PTR)[-1]. *PTR will be updated to point to just after the
1641 last character of the sequence. If OUTPUT is not NULL, the
1642 translated form of the escape sequence will be written there. If
1643 OUTPUT is NULL, no output is written and the call will only affect
1644 *PTR. If an escape sequence is expressed in target bytes, then the
1645 entire sequence will simply be copied to OUTPUT. Return 1 if any
1646 character was emitted, 0 otherwise. */
1649 c_parse_escape (char **ptr, struct obstack *output)
1651 char *tokptr = *ptr;
1654 /* Some escape sequences undergo character set conversion. Those we
1658 /* Hex escapes do not undergo character set conversion, so keep
1659 the escape sequence for later. */
1662 obstack_grow_str (output, "\\x");
1664 if (!isxdigit (*tokptr))
1665 error (_("\\x escape without a following hex digit"));
1666 while (isxdigit (*tokptr))
1669 obstack_1grow (output, *tokptr);
1674 /* Octal escapes do not undergo character set conversion, so
1675 keep the escape sequence for later. */
1687 obstack_grow_str (output, "\\");
1689 i < 3 && isdigit (*tokptr) && *tokptr != '8' && *tokptr != '9';
1693 obstack_1grow (output, *tokptr);
1699 /* We handle UCNs later. We could handle them here, but that
1700 would mean a spurious error in the case where the UCN could
1701 be converted to the target charset but not the host
1707 int i, len = c == 'U' ? 8 : 4;
1710 obstack_1grow (output, '\\');
1711 obstack_1grow (output, *tokptr);
1714 if (!isxdigit (*tokptr))
1715 error (_("\\%c escape without a following hex digit"), c);
1716 for (i = 0; i < len && isxdigit (*tokptr); ++i)
1719 obstack_1grow (output, *tokptr);
1725 /* We must pass backslash through so that it does not
1726 cause quoting during the second expansion. */
1729 obstack_grow_str (output, "\\\\");
1733 /* Escapes which undergo conversion. */
1736 obstack_1grow (output, '\a');
1741 obstack_1grow (output, '\b');
1746 obstack_1grow (output, '\f');
1751 obstack_1grow (output, '\n');
1756 obstack_1grow (output, '\r');
1761 obstack_1grow (output, '\t');
1766 obstack_1grow (output, '\v');
1770 /* GCC extension. */
1773 obstack_1grow (output, HOST_ESCAPE_CHAR);
1777 /* Backslash-newline expands to nothing at all. */
1783 /* A few escapes just expand to the character itself. */
1787 /* GCC extensions. */
1792 /* Unrecognized escapes turn into the character itself. */
1795 obstack_1grow (output, *tokptr);
1803 /* Parse a string or character literal from TOKPTR. The string or
1804 character may be wide or unicode. *OUTPTR is set to just after the
1805 end of the literal in the input string. The resulting token is
1806 stored in VALUE. This returns a token value, either STRING or
1807 CHAR, depending on what was parsed. *HOST_CHARS is set to the
1808 number of host characters in the literal. */
1810 parse_string_or_char (char *tokptr, char **outptr, struct typed_stoken *value,
1814 enum c_string_type type;
1816 /* Build the gdb internal form of the input string in tempbuf. Note
1817 that the buffer is null byte terminated *only* for the
1818 convenience of debugging gdb itself and printing the buffer
1819 contents when the buffer contains no embedded nulls. Gdb does
1820 not depend upon the buffer being null byte terminated, it uses
1821 the length string instead. This allows gdb to handle C strings
1822 (as well as strings in other languages) with embedded null
1828 obstack_free (&tempbuf, NULL);
1829 obstack_init (&tempbuf);
1831 /* Record the string type. */
1834 type = C_WIDE_STRING;
1837 else if (*tokptr == 'u')
1842 else if (*tokptr == 'U')
1850 /* Skip the quote. */
1864 *host_chars += c_parse_escape (&tokptr, &tempbuf);
1866 else if (c == quote)
1870 obstack_1grow (&tempbuf, c);
1872 /* FIXME: this does the wrong thing with multi-byte host
1873 characters. We could use mbrlen here, but that would
1874 make "set host-charset" a bit less useful. */
1879 if (*tokptr != quote)
1882 error (_("Unterminated string in expression."));
1884 error (_("Unmatched single quote."));
1889 value->ptr = obstack_base (&tempbuf);
1890 value->length = obstack_object_size (&tempbuf);
1894 return quote == '"' ? STRING : CHAR;
1901 enum exp_opcode opcode;
1905 static const struct token tokentab3[] =
1907 {">>=", ASSIGN_MODIFY, BINOP_RSH, 0},
1908 {"<<=", ASSIGN_MODIFY, BINOP_LSH, 0},
1909 {"->*", ARROW_STAR, BINOP_END, 1}
1912 static const struct token tokentab2[] =
1914 {"+=", ASSIGN_MODIFY, BINOP_ADD, 0},
1915 {"-=", ASSIGN_MODIFY, BINOP_SUB, 0},
1916 {"*=", ASSIGN_MODIFY, BINOP_MUL, 0},
1917 {"/=", ASSIGN_MODIFY, BINOP_DIV, 0},
1918 {"%=", ASSIGN_MODIFY, BINOP_REM, 0},
1919 {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR, 0},
1920 {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND, 0},
1921 {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR, 0},
1922 {"++", INCREMENT, BINOP_END, 0},
1923 {"--", DECREMENT, BINOP_END, 0},
1924 {"->", ARROW, BINOP_END, 0},
1925 {"&&", ANDAND, BINOP_END, 0},
1926 {"||", OROR, BINOP_END, 0},
1927 /* "::" is *not* only C++: gdb overrides its meaning in several
1928 different ways, e.g., 'filename'::func, function::variable. */
1929 {"::", COLONCOLON, BINOP_END, 0},
1930 {"<<", LSH, BINOP_END, 0},
1931 {">>", RSH, BINOP_END, 0},
1932 {"==", EQUAL, BINOP_END, 0},
1933 {"!=", NOTEQUAL, BINOP_END, 0},
1934 {"<=", LEQ, BINOP_END, 0},
1935 {">=", GEQ, BINOP_END, 0},
1936 {".*", DOT_STAR, BINOP_END, 1}
1939 /* Identifier-like tokens. */
1940 static const struct token ident_tokens[] =
1942 {"unsigned", UNSIGNED, OP_NULL, 0},
1943 {"template", TEMPLATE, OP_NULL, 1},
1944 {"volatile", VOLATILE_KEYWORD, OP_NULL, 0},
1945 {"struct", STRUCT, OP_NULL, 0},
1946 {"signed", SIGNED_KEYWORD, OP_NULL, 0},
1947 {"sizeof", SIZEOF, OP_NULL, 0},
1948 {"double", DOUBLE_KEYWORD, OP_NULL, 0},
1949 {"false", FALSEKEYWORD, OP_NULL, 1},
1950 {"class", CLASS, OP_NULL, 1},
1951 {"union", UNION, OP_NULL, 0},
1952 {"short", SHORT, OP_NULL, 0},
1953 {"const", CONST_KEYWORD, OP_NULL, 0},
1954 {"enum", ENUM, OP_NULL, 0},
1955 {"long", LONG, OP_NULL, 0},
1956 {"true", TRUEKEYWORD, OP_NULL, 1},
1957 {"int", INT_KEYWORD, OP_NULL, 0},
1958 {"new", NEW, OP_NULL, 1},
1959 {"delete", DELETE, OP_NULL, 1},
1960 {"operator", OPERATOR, OP_NULL, 1},
1962 {"and", ANDAND, BINOP_END, 1},
1963 {"and_eq", ASSIGN_MODIFY, BINOP_BITWISE_AND, 1},
1964 {"bitand", '&', OP_NULL, 1},
1965 {"bitor", '|', OP_NULL, 1},
1966 {"compl", '~', OP_NULL, 1},
1967 {"not", '!', OP_NULL, 1},
1968 {"not_eq", NOTEQUAL, BINOP_END, 1},
1969 {"or", OROR, BINOP_END, 1},
1970 {"or_eq", ASSIGN_MODIFY, BINOP_BITWISE_IOR, 1},
1971 {"xor", '^', OP_NULL, 1},
1972 {"xor_eq", ASSIGN_MODIFY, BINOP_BITWISE_XOR, 1},
1974 {"const_cast", CONST_CAST, OP_NULL, 1 },
1975 {"dynamic_cast", DYNAMIC_CAST, OP_NULL, 1 },
1976 {"static_cast", STATIC_CAST, OP_NULL, 1 },
1977 {"reinterpret_cast", REINTERPRET_CAST, OP_NULL, 1 }
1980 /* When we find that lexptr (the global var defined in parse.c) is
1981 pointing at a macro invocation, we expand the invocation, and call
1982 scan_macro_expansion to save the old lexptr here and point lexptr
1983 into the expanded text. When we reach the end of that, we call
1984 end_macro_expansion to pop back to the value we saved here. The
1985 macro expansion code promises to return only fully-expanded text,
1986 so we don't need to "push" more than one level.
1988 This is disgusting, of course. It would be cleaner to do all macro
1989 expansion beforehand, and then hand that to lexptr. But we don't
1990 really know where the expression ends. Remember, in a command like
1992 (gdb) break *ADDRESS if CONDITION
1994 we evaluate ADDRESS in the scope of the current frame, but we
1995 evaluate CONDITION in the scope of the breakpoint's location. So
1996 it's simply wrong to try to macro-expand the whole thing at once. */
1997 static char *macro_original_text;
1999 /* We save all intermediate macro expansions on this obstack for the
2000 duration of a single parse. The expansion text may sometimes have
2001 to live past the end of the expansion, due to yacc lookahead.
2002 Rather than try to be clever about saving the data for a single
2003 token, we simply keep it all and delete it after parsing has
2005 static struct obstack expansion_obstack;
2008 scan_macro_expansion (char *expansion)
2012 /* We'd better not be trying to push the stack twice. */
2013 gdb_assert (! macro_original_text);
2015 /* Copy to the obstack, and then free the intermediate
2017 copy = obstack_copy0 (&expansion_obstack, expansion, strlen (expansion));
2020 /* Save the old lexptr value, so we can return to it when we're done
2021 parsing the expanded text. */
2022 macro_original_text = lexptr;
2028 scanning_macro_expansion (void)
2030 return macro_original_text != 0;
2035 finished_macro_expansion (void)
2037 /* There'd better be something to pop back to. */
2038 gdb_assert (macro_original_text);
2040 /* Pop back to the original text. */
2041 lexptr = macro_original_text;
2042 macro_original_text = 0;
2047 scan_macro_cleanup (void *dummy)
2049 if (macro_original_text)
2050 finished_macro_expansion ();
2052 obstack_free (&expansion_obstack, NULL);
2055 /* Return true iff the token represents a C++ cast operator. */
2058 is_cast_operator (const char *token, int len)
2060 return (! strncmp (token, "dynamic_cast", len)
2061 || ! strncmp (token, "static_cast", len)
2062 || ! strncmp (token, "reinterpret_cast", len)
2063 || ! strncmp (token, "const_cast", len));
2066 /* The scope used for macro expansion. */
2067 static struct macro_scope *expression_macro_scope;
2069 /* This is set if a NAME token appeared at the very end of the input
2070 string, with no whitespace separating the name from the EOF. This
2071 is used only when parsing to do field name completion. */
2072 static int saw_name_at_eof;
2074 /* This is set if the previously-returned token was a structure
2075 operator -- either '.' or ARROW. This is used only when parsing to
2076 do field name completion. */
2077 static int last_was_structop;
2079 /* Read one token, getting characters through lexptr. */
2082 lex_one_token (void)
2088 int saw_structop = last_was_structop;
2091 last_was_structop = 0;
2095 /* Check if this is a macro invocation that we need to expand. */
2096 if (! scanning_macro_expansion ())
2098 char *expanded = macro_expand_next (&lexptr,
2099 standard_macro_lookup,
2100 expression_macro_scope);
2103 scan_macro_expansion (expanded);
2106 prev_lexptr = lexptr;
2109 /* See if it is a special token of length 3. */
2110 for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
2111 if (strncmp (tokstart, tokentab3[i].operator, 3) == 0)
2113 if (tokentab3[i].cxx_only
2114 && parse_language->la_language != language_cplus)
2118 yylval.opcode = tokentab3[i].opcode;
2119 return tokentab3[i].token;
2122 /* See if it is a special token of length 2. */
2123 for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
2124 if (strncmp (tokstart, tokentab2[i].operator, 2) == 0)
2126 if (tokentab2[i].cxx_only
2127 && parse_language->la_language != language_cplus)
2131 yylval.opcode = tokentab2[i].opcode;
2132 if (in_parse_field && tokentab2[i].token == ARROW)
2133 last_was_structop = 1;
2134 return tokentab2[i].token;
2137 switch (c = *tokstart)
2140 /* If we were just scanning the result of a macro expansion,
2141 then we need to resume scanning the original text.
2142 If we're parsing for field name completion, and the previous
2143 token allows such completion, return a COMPLETE token.
2144 Otherwise, we were already scanning the original text, and
2145 we're really done. */
2146 if (scanning_macro_expansion ())
2148 finished_macro_expansion ();
2151 else if (saw_name_at_eof)
2153 saw_name_at_eof = 0;
2156 else if (saw_structop)
2175 if (paren_depth == 0)
2182 if (comma_terminates
2184 && ! scanning_macro_expansion ())
2190 /* Might be a floating point number. */
2191 if (lexptr[1] < '0' || lexptr[1] > '9')
2194 last_was_structop = 1;
2195 goto symbol; /* Nope, must be a symbol. */
2197 /* FALL THRU into number case. */
2210 /* It's a number. */
2211 int got_dot = 0, got_e = 0, toktype;
2213 int hex = input_radix > 10;
2215 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
2220 else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
2228 /* This test includes !hex because 'e' is a valid hex digit
2229 and thus does not indicate a floating point number when
2230 the radix is hex. */
2231 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
2232 got_dot = got_e = 1;
2233 /* This test does not include !hex, because a '.' always indicates
2234 a decimal floating point number regardless of the radix. */
2235 else if (!got_dot && *p == '.')
2237 else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
2238 && (*p == '-' || *p == '+'))
2239 /* This is the sign of the exponent, not the end of the
2242 /* We will take any letters or digits. parse_number will
2243 complain if past the radix, or if L or U are not final. */
2244 else if ((*p < '0' || *p > '9')
2245 && ((*p < 'a' || *p > 'z')
2246 && (*p < 'A' || *p > 'Z')))
2249 toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
2250 if (toktype == ERROR)
2252 char *err_copy = (char *) alloca (p - tokstart + 1);
2254 memcpy (err_copy, tokstart, p - tokstart);
2255 err_copy[p - tokstart] = 0;
2256 error (_("Invalid number \"%s\"."), err_copy);
2264 char *p = &tokstart[1];
2265 size_t len = strlen ("entry");
2267 while (isspace (*p))
2269 if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
2301 if (tokstart[1] != '"' && tokstart[1] != '\'')
2308 int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
2313 error (_("Empty character constant."));
2314 else if (host_len > 2 && c == '\'')
2317 namelen = lexptr - tokstart - 1;
2320 else if (host_len > 1)
2321 error (_("Invalid character constant."));
2327 if (!(c == '_' || c == '$'
2328 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
2329 /* We must have come across a bad character (e.g. ';'). */
2330 error (_("Invalid character '%c' in expression."), c);
2332 /* It's a name. See how long it is. */
2334 for (c = tokstart[namelen];
2335 (c == '_' || c == '$' || (c >= '0' && c <= '9')
2336 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z') || c == '<');)
2338 /* Template parameter lists are part of the name.
2339 FIXME: This mishandles `print $a<4&&$a>3'. */
2343 if (! is_cast_operator (tokstart, namelen))
2345 /* Scan ahead to get rest of the template specification. Note
2346 that we look ahead only when the '<' adjoins non-whitespace
2347 characters; for comparison expressions, e.g. "a < b > c",
2348 there must be spaces before the '<', etc. */
2350 char * p = find_template_name_end (tokstart + namelen);
2352 namelen = p - tokstart;
2356 c = tokstart[++namelen];
2359 /* The token "if" terminates the expression and is NOT removed from
2360 the input stream. It doesn't count if it appears in the
2361 expansion of a macro. */
2363 && tokstart[0] == 'i'
2364 && tokstart[1] == 'f'
2365 && ! scanning_macro_expansion ())
2370 /* For the same reason (breakpoint conditions), "thread N"
2371 terminates the expression. "thread" could be an identifier, but
2372 an identifier is never followed by a number without intervening
2373 punctuation. "task" is similar. Handle abbreviations of these,
2374 similarly to breakpoint.c:find_condition_and_thread. */
2376 && (strncmp (tokstart, "thread", namelen) == 0
2377 || strncmp (tokstart, "task", namelen) == 0)
2378 && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t')
2379 && ! scanning_macro_expansion ())
2381 char *p = tokstart + namelen + 1;
2382 while (*p == ' ' || *p == '\t')
2384 if (*p >= '0' && *p <= '9')
2392 yylval.sval.ptr = tokstart;
2393 yylval.sval.length = namelen;
2395 /* Catch specific keywords. */
2396 copy = copy_name (yylval.sval);
2397 for (i = 0; i < sizeof ident_tokens / sizeof ident_tokens[0]; i++)
2398 if (strcmp (copy, ident_tokens[i].operator) == 0)
2400 if (ident_tokens[i].cxx_only
2401 && parse_language->la_language != language_cplus)
2404 /* It is ok to always set this, even though we don't always
2405 strictly need to. */
2406 yylval.opcode = ident_tokens[i].opcode;
2407 return ident_tokens[i].token;
2410 if (*tokstart == '$')
2413 if (in_parse_field && *lexptr == '\0')
2414 saw_name_at_eof = 1;
2418 /* An object of this type is pushed on a FIFO by the "outer" lexer. */
2425 DEF_VEC_O (token_and_value);
2427 /* A FIFO of tokens that have been read but not yet returned to the
2429 static VEC (token_and_value) *token_fifo;
2431 /* Non-zero if the lexer should return tokens from the FIFO. */
2434 /* Temporary storage for c_lex; this holds symbol names as they are
2436 static struct obstack name_obstack;
2438 /* Classify a NAME token. The contents of the token are in `yylval'.
2439 Updates yylval and returns the new token type. BLOCK is the block
2440 in which lookups start; this can be NULL to mean the global
2443 classify_name (struct block *block)
2447 int is_a_field_of_this = 0;
2449 copy = copy_name (yylval.sval);
2451 sym = lookup_symbol (copy, block, VAR_DOMAIN,
2452 parse_language->la_language == language_cplus
2453 ? &is_a_field_of_this : (int *) NULL);
2455 if (sym && SYMBOL_CLASS (sym) == LOC_BLOCK)
2457 yylval.ssym.sym = sym;
2458 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
2463 /* See if it's a file name. */
2464 struct symtab *symtab;
2466 symtab = lookup_symtab (copy);
2469 yylval.bval = BLOCKVECTOR_BLOCK (BLOCKVECTOR (symtab), STATIC_BLOCK);
2474 if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
2476 yylval.tsym.type = SYMBOL_TYPE (sym);
2481 = language_lookup_primitive_type_by_name (parse_language,
2482 parse_gdbarch, copy);
2483 if (yylval.tsym.type != NULL)
2486 /* Input names that aren't symbols but ARE valid hex numbers, when
2487 the input radix permits them, can be names or numbers depending
2488 on the parse. Note we support radixes > 16 here. */
2490 && ((copy[0] >= 'a' && copy[0] < 'a' + input_radix - 10)
2491 || (copy[0] >= 'A' && copy[0] < 'A' + input_radix - 10)))
2493 YYSTYPE newlval; /* Its value is ignored. */
2494 int hextype = parse_number (copy, yylval.sval.length, 0, &newlval);
2497 yylval.ssym.sym = sym;
2498 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
2503 /* Any other kind of symbol */
2504 yylval.ssym.sym = sym;
2505 yylval.ssym.is_a_field_of_this = is_a_field_of_this;
2508 && parse_language->la_language == language_cplus
2509 && !is_a_field_of_this
2510 && !lookup_minimal_symbol (copy, NULL, NULL))
2511 return UNKNOWN_CPP_NAME;
2516 /* Like classify_name, but used by the inner loop of the lexer, when a
2517 name might have already been seen. FIRST_NAME is true if the token
2518 in `yylval' is the first component of a name, false otherwise. */
2521 classify_inner_name (struct block *block, int first_name)
2523 struct type *type, *new_type;
2527 return classify_name (block);
2529 type = check_typedef (yylval.tsym.type);
2530 if (TYPE_CODE (type) != TYPE_CODE_STRUCT
2531 && TYPE_CODE (type) != TYPE_CODE_UNION
2532 && TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
2535 copy = copy_name (yylval.tsym.stoken);
2536 yylval.ssym.sym = cp_lookup_nested_symbol (yylval.tsym.type, copy, block);
2537 if (yylval.ssym.sym == NULL)
2540 switch (SYMBOL_CLASS (yylval.ssym.sym))
2547 yylval.tsym.type = SYMBOL_TYPE (yylval.ssym.sym);;
2551 yylval.ssym.is_a_field_of_this = 0;
2554 internal_error (__FILE__, __LINE__, _("not reached"));
2557 /* The outer level of a two-level lexer. This calls the inner lexer
2558 to return tokens. It then either returns these tokens, or
2559 aggregates them into a larger token. This lets us work around a
2560 problem in our parsing approach, where the parser could not
2561 distinguish between qualified names and qualified types at the
2564 This approach is still not ideal, because it mishandles template
2565 types. See the comment in lex_one_token for an example. However,
2566 this is still an improvement over the earlier approach, and will
2567 suffice until we move to better parsing technology. */
2571 token_and_value current;
2572 int first_was_coloncolon, last_was_coloncolon, first_iter;
2574 if (popping && !VEC_empty (token_and_value, token_fifo))
2576 token_and_value tv = *VEC_index (token_and_value, token_fifo, 0);
2577 VEC_ordered_remove (token_and_value, token_fifo, 0);
2583 current.token = lex_one_token ();
2584 if (current.token == NAME)
2585 current.token = classify_name (expression_context_block);
2586 if (parse_language->la_language != language_cplus
2587 || (current.token != TYPENAME && current.token != COLONCOLON))
2588 return current.token;
2590 first_was_coloncolon = current.token == COLONCOLON;
2591 last_was_coloncolon = first_was_coloncolon;
2592 obstack_free (&name_obstack, obstack_base (&name_obstack));
2593 if (!last_was_coloncolon)
2594 obstack_grow (&name_obstack, yylval.sval.ptr, yylval.sval.length);
2595 current.value = yylval;
2599 token_and_value next;
2601 next.token = lex_one_token ();
2602 next.value = yylval;
2604 if (next.token == NAME && last_was_coloncolon)
2608 classification = classify_inner_name (first_was_coloncolon
2610 : expression_context_block,
2612 /* We keep going until we either run out of names, or until
2613 we have a qualified name which is not a type. */
2614 if (classification != TYPENAME && classification != NAME)
2616 /* Push the final component and leave the loop. */
2617 VEC_safe_push (token_and_value, token_fifo, &next);
2621 /* Update the partial name we are constructing. */
2624 /* We don't want to put a leading "::" into the name. */
2625 obstack_grow_str (&name_obstack, "::");
2627 obstack_grow (&name_obstack, next.value.sval.ptr,
2628 next.value.sval.length);
2630 yylval.sval.ptr = obstack_base (&name_obstack);
2631 yylval.sval.length = obstack_object_size (&name_obstack);
2632 current.value = yylval;
2633 current.token = classification;
2635 last_was_coloncolon = 0;
2637 else if (next.token == COLONCOLON && !last_was_coloncolon)
2638 last_was_coloncolon = 1;
2641 /* We've reached the end of the name. */
2642 VEC_safe_push (token_and_value, token_fifo, &next);
2651 /* If we ended with a "::", insert it too. */
2652 if (last_was_coloncolon)
2655 memset (&cc, 0, sizeof (token_and_value));
2656 if (first_was_coloncolon && first_iter)
2661 cc.token = COLONCOLON;
2662 VEC_safe_insert (token_and_value, token_fifo, 0, &cc);
2665 yylval = current.value;
2666 yylval.sval.ptr = obstack_copy0 (&expansion_obstack,
2668 yylval.sval.length);
2669 return current.token;
2676 struct cleanup *back_to = make_cleanup (free_current_contents,
2677 &expression_macro_scope);
2679 /* Set up the scope for macro expansion. */
2680 expression_macro_scope = NULL;
2682 if (expression_context_block)
2683 expression_macro_scope
2684 = sal_macro_scope (find_pc_line (expression_context_pc, 0));
2686 expression_macro_scope = default_macro_scope ();
2687 if (! expression_macro_scope)
2688 expression_macro_scope = user_macro_scope ();
2690 /* Initialize macro expansion code. */
2691 obstack_init (&expansion_obstack);
2692 gdb_assert (! macro_original_text);
2693 make_cleanup (scan_macro_cleanup, 0);
2695 make_cleanup_restore_integer (&yydebug);
2696 yydebug = parser_debug;
2698 /* Initialize some state used by the lexer. */
2699 last_was_structop = 0;
2700 saw_name_at_eof = 0;
2702 VEC_free (token_and_value, token_fifo);
2704 obstack_init (&name_obstack);
2705 make_cleanup_obstack_free (&name_obstack);
2707 result = yyparse ();
2708 do_cleanups (back_to);
2717 lexptr = prev_lexptr;
2719 error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);