2 /* YACC parser for Fortran expressions, for GDB.
3 Copyright (C) 1986-2017 Free Software Foundation, Inc.
5 Contributed by Motorola. Adapted from the C parser by Farooq Butt
6 (fmbutt@engage.sps.mot.com).
8 This file is part of GDB.
10 This program is free software; you can redistribute it and/or modify
11 it under the terms of the GNU General Public License as published by
12 the Free Software Foundation; either version 3 of the License, or
13 (at your option) any later version.
15 This program is distributed in the hope that it will be useful,
16 but WITHOUT ANY WARRANTY; without even the implied warranty of
17 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
18 GNU General Public License for more details.
20 You should have received a copy of the GNU General Public License
21 along with this program. If not, see <http://www.gnu.org/licenses/>. */
23 /* This was blantantly ripped off the C expression parser, please
24 be aware of that as you look at its basic structure -FMB */
26 /* Parse a F77 expression from text in a string,
27 and return the result as a struct expression pointer.
28 That structure contains arithmetic operations in reverse polish,
29 with constants represented by operations that are followed by special data.
30 See expression.h for the details of the format.
31 What is important here is that it can be built up sequentially
32 during the process of parsing; the lower levels of the tree always
33 come first in the result.
35 Note that malloc's and realloc's in this file are transformed to
36 xmalloc and xrealloc respectively by the same sed command in the
37 makefile that remaps any other malloc/realloc inserted by the parser
38 generator. Doing this with #defines and trying to control the interaction
39 with include files (<malloc.h> and <stdlib.h> for example) just became
40 too messy, particularly when such includes can be inserted at random
41 times by the parser generator. */
46 #include "expression.h"
48 #include "parser-defs.h"
51 #include "bfd.h" /* Required by objfiles.h. */
52 #include "symfile.h" /* Required by objfiles.h. */
53 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
58 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
59 #define parse_f_type(ps) builtin_f_type (parse_gdbarch (ps))
61 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror,
63 #define GDB_YY_REMAP_PREFIX f_
66 /* The state of the parser, used internally when we are parsing the
69 static struct parser_state *pstate = NULL;
73 static int yylex (void);
75 void yyerror (const char *);
77 static void growbuf_by_size (int);
79 static int match_string_literal (void);
83 /* Although the yacc "value" of an expression is not used,
84 since the result is stored in the structure being created,
85 other node types do have values. */
102 struct symtoken ssym;
105 enum exp_opcode opcode;
106 struct internalvar *ivar;
113 /* YYSTYPE gets defined by %union */
114 static int parse_number (struct parser_state *, const char *, int,
118 %type <voidval> exp type_exp start variable
119 %type <tval> type typebase
120 %type <tvec> nonempty_typelist
121 /* %type <bval> block */
123 /* Fancy type parsing. */
124 %type <voidval> func_mod direct_abs_decl abs_decl
127 %token <typed_val> INT
128 %token <typed_val_float> FLOAT
130 /* Both NAME and TYPENAME tokens represent symbols in the input,
131 and both convey their data as strings.
132 But a TYPENAME is a string that happens to be defined as a typedef
133 or builtin type name (such as int or char)
134 and a NAME is any other symbol.
135 Contexts where this distinction is not important can use the
136 nonterminal "name", which matches either NAME or TYPENAME. */
138 %token <sval> STRING_LITERAL
139 %token <lval> BOOLEAN_LITERAL
141 %token <tsym> TYPENAME
143 %type <ssym> name_not_typename
145 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
146 but which would parse as a valid number in the current input radix.
147 E.g. "c" when input_radix==16. Depending on the parse, it will be
148 turned into a name or into a number. */
150 %token <ssym> NAME_OR_INT
155 /* Special type cases, put in to allow the parser to distinguish different
157 %token INT_KEYWORD INT_S2_KEYWORD LOGICAL_S1_KEYWORD LOGICAL_S2_KEYWORD
158 %token LOGICAL_S8_KEYWORD
159 %token LOGICAL_KEYWORD REAL_KEYWORD REAL_S8_KEYWORD REAL_S16_KEYWORD
160 %token COMPLEX_S8_KEYWORD COMPLEX_S16_KEYWORD COMPLEX_S32_KEYWORD
161 %token BOOL_AND BOOL_OR BOOL_NOT
162 %token <lval> CHARACTER
164 %token <voidval> VARIABLE
166 %token <opcode> ASSIGN_MODIFY
170 %right '=' ASSIGN_MODIFY
179 %left LESSTHAN GREATERTHAN LEQ GEQ
197 { write_exp_elt_opcode (pstate, OP_TYPE);
198 write_exp_elt_type (pstate, $1);
199 write_exp_elt_opcode (pstate, OP_TYPE); }
206 /* Expressions, not including the comma operator. */
207 exp : '*' exp %prec UNARY
208 { write_exp_elt_opcode (pstate, UNOP_IND); }
211 exp : '&' exp %prec UNARY
212 { write_exp_elt_opcode (pstate, UNOP_ADDR); }
215 exp : '-' exp %prec UNARY
216 { write_exp_elt_opcode (pstate, UNOP_NEG); }
219 exp : BOOL_NOT exp %prec UNARY
220 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
223 exp : '~' exp %prec UNARY
224 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
227 exp : SIZEOF exp %prec UNARY
228 { write_exp_elt_opcode (pstate, UNOP_SIZEOF); }
231 /* No more explicit array operators, we treat everything in F77 as
232 a function call. The disambiguation as to whether we are
233 doing a subscript operation or a function call is done
237 { start_arglist (); }
239 { write_exp_elt_opcode (pstate,
240 OP_F77_UNDETERMINED_ARGLIST);
241 write_exp_elt_longcst (pstate,
242 (LONGEST) end_arglist ());
243 write_exp_elt_opcode (pstate,
244 OP_F77_UNDETERMINED_ARGLIST); }
258 arglist : arglist ',' exp %prec ABOVE_COMMA
262 /* There are four sorts of subrange types in F90. */
264 subrange: exp ':' exp %prec ABOVE_COMMA
265 { write_exp_elt_opcode (pstate, OP_RANGE);
266 write_exp_elt_longcst (pstate, NONE_BOUND_DEFAULT);
267 write_exp_elt_opcode (pstate, OP_RANGE); }
270 subrange: exp ':' %prec ABOVE_COMMA
271 { write_exp_elt_opcode (pstate, OP_RANGE);
272 write_exp_elt_longcst (pstate, HIGH_BOUND_DEFAULT);
273 write_exp_elt_opcode (pstate, OP_RANGE); }
276 subrange: ':' exp %prec ABOVE_COMMA
277 { write_exp_elt_opcode (pstate, OP_RANGE);
278 write_exp_elt_longcst (pstate, LOW_BOUND_DEFAULT);
279 write_exp_elt_opcode (pstate, OP_RANGE); }
282 subrange: ':' %prec ABOVE_COMMA
283 { write_exp_elt_opcode (pstate, OP_RANGE);
284 write_exp_elt_longcst (pstate, BOTH_BOUND_DEFAULT);
285 write_exp_elt_opcode (pstate, OP_RANGE); }
288 complexnum: exp ',' exp
292 exp : '(' complexnum ')'
293 { write_exp_elt_opcode (pstate, OP_COMPLEX);
294 write_exp_elt_type (pstate,
295 parse_f_type (pstate)
296 ->builtin_complex_s16);
297 write_exp_elt_opcode (pstate, OP_COMPLEX); }
300 exp : '(' type ')' exp %prec UNARY
301 { write_exp_elt_opcode (pstate, UNOP_CAST);
302 write_exp_elt_type (pstate, $2);
303 write_exp_elt_opcode (pstate, UNOP_CAST); }
307 { write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
308 write_exp_string (pstate, $3);
309 write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
312 /* Binary operators in order of decreasing precedence. */
315 { write_exp_elt_opcode (pstate, BINOP_REPEAT); }
318 exp : exp STARSTAR exp
319 { write_exp_elt_opcode (pstate, BINOP_EXP); }
323 { write_exp_elt_opcode (pstate, BINOP_MUL); }
327 { write_exp_elt_opcode (pstate, BINOP_DIV); }
331 { write_exp_elt_opcode (pstate, BINOP_ADD); }
335 { write_exp_elt_opcode (pstate, BINOP_SUB); }
339 { write_exp_elt_opcode (pstate, BINOP_LSH); }
343 { write_exp_elt_opcode (pstate, BINOP_RSH); }
347 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
350 exp : exp NOTEQUAL exp
351 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
355 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
359 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
362 exp : exp LESSTHAN exp
363 { write_exp_elt_opcode (pstate, BINOP_LESS); }
366 exp : exp GREATERTHAN exp
367 { write_exp_elt_opcode (pstate, BINOP_GTR); }
371 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
375 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
379 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
382 exp : exp BOOL_AND exp
383 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
387 exp : exp BOOL_OR exp
388 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
392 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
395 exp : exp ASSIGN_MODIFY exp
396 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
397 write_exp_elt_opcode (pstate, $2);
398 write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
402 { write_exp_elt_opcode (pstate, OP_LONG);
403 write_exp_elt_type (pstate, $1.type);
404 write_exp_elt_longcst (pstate, (LONGEST) ($1.val));
405 write_exp_elt_opcode (pstate, OP_LONG); }
410 parse_number (pstate, $1.stoken.ptr,
411 $1.stoken.length, 0, &val);
412 write_exp_elt_opcode (pstate, OP_LONG);
413 write_exp_elt_type (pstate, val.typed_val.type);
414 write_exp_elt_longcst (pstate,
415 (LONGEST)val.typed_val.val);
416 write_exp_elt_opcode (pstate, OP_LONG); }
420 { write_exp_elt_opcode (pstate, OP_FLOAT);
421 write_exp_elt_type (pstate, $1.type);
422 write_exp_elt_floatcst (pstate, $1.val);
423 write_exp_elt_opcode (pstate, OP_FLOAT); }
432 exp : SIZEOF '(' type ')' %prec UNARY
433 { write_exp_elt_opcode (pstate, OP_LONG);
434 write_exp_elt_type (pstate,
435 parse_f_type (pstate)
437 $3 = check_typedef ($3);
438 write_exp_elt_longcst (pstate,
439 (LONGEST) TYPE_LENGTH ($3));
440 write_exp_elt_opcode (pstate, OP_LONG); }
443 exp : BOOLEAN_LITERAL
444 { write_exp_elt_opcode (pstate, OP_BOOL);
445 write_exp_elt_longcst (pstate, (LONGEST) $1);
446 write_exp_elt_opcode (pstate, OP_BOOL);
452 write_exp_elt_opcode (pstate, OP_STRING);
453 write_exp_string (pstate, $1);
454 write_exp_elt_opcode (pstate, OP_STRING);
458 variable: name_not_typename
459 { struct block_symbol sym = $1.sym;
463 if (symbol_read_needs_frame (sym.symbol))
465 if (innermost_block == 0
466 || contained_in (sym.block,
468 innermost_block = sym.block;
470 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
471 write_exp_elt_block (pstate, sym.block);
472 write_exp_elt_sym (pstate, sym.symbol);
473 write_exp_elt_opcode (pstate, OP_VAR_VALUE);
478 struct bound_minimal_symbol msymbol;
479 char *arg = copy_name ($1.stoken);
482 lookup_bound_minimal_symbol (arg);
483 if (msymbol.minsym != NULL)
484 write_exp_msymbol (pstate, msymbol);
485 else if (!have_full_symbols () && !have_partial_symbols ())
486 error (_("No symbol table is loaded. Use the \"file\" command."));
488 error (_("No symbol \"%s\" in current context."),
489 copy_name ($1.stoken));
501 /* This is where the interesting stuff happens. */
504 struct type *follow_type = $1;
505 struct type *range_type;
514 follow_type = lookup_pointer_type (follow_type);
517 follow_type = lookup_lvalue_reference_type (follow_type);
520 array_size = pop_type_int ();
521 if (array_size != -1)
524 create_static_range_type ((struct type *) NULL,
525 parse_f_type (pstate)
529 create_array_type ((struct type *) NULL,
530 follow_type, range_type);
533 follow_type = lookup_pointer_type (follow_type);
536 follow_type = lookup_function_type (follow_type);
544 { push_type (tp_pointer); $$ = 0; }
546 { push_type (tp_pointer); $$ = $2; }
548 { push_type (tp_reference); $$ = 0; }
550 { push_type (tp_reference); $$ = $2; }
554 direct_abs_decl: '(' abs_decl ')'
556 | direct_abs_decl func_mod
557 { push_type (tp_function); }
559 { push_type (tp_function); }
564 | '(' nonempty_typelist ')'
565 { free ($2); $$ = 0; }
568 typebase /* Implements (approximately): (type-qualifier)* type-specifier */
572 { $$ = parse_f_type (pstate)->builtin_integer; }
574 { $$ = parse_f_type (pstate)->builtin_integer_s2; }
576 { $$ = parse_f_type (pstate)->builtin_character; }
578 { $$ = parse_f_type (pstate)->builtin_logical_s8; }
580 { $$ = parse_f_type (pstate)->builtin_logical; }
582 { $$ = parse_f_type (pstate)->builtin_logical_s2; }
584 { $$ = parse_f_type (pstate)->builtin_logical_s1; }
586 { $$ = parse_f_type (pstate)->builtin_real; }
588 { $$ = parse_f_type (pstate)->builtin_real_s8; }
590 { $$ = parse_f_type (pstate)->builtin_real_s16; }
592 { $$ = parse_f_type (pstate)->builtin_complex_s8; }
593 | COMPLEX_S16_KEYWORD
594 { $$ = parse_f_type (pstate)->builtin_complex_s16; }
595 | COMPLEX_S32_KEYWORD
596 { $$ = parse_f_type (pstate)->builtin_complex_s32; }
601 { $$ = (struct type **) malloc (sizeof (struct type *) * 2);
602 $<ivec>$[0] = 1; /* Number of types in vector */
605 | nonempty_typelist ',' type
606 { int len = sizeof (struct type *) * (++($<ivec>1[0]) + 1);
607 $$ = (struct type **) realloc ((char *) $1, len);
608 $$[$<ivec>$[0]] = $3;
616 name_not_typename : NAME
617 /* These would be useful if name_not_typename was useful, but it is just
618 a fake for "variable", so these cause reduce/reduce conflicts because
619 the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
620 =exp) or just an exp. If name_not_typename was ever used in an lvalue
621 context where only a name could occur, this might be useful.
628 /* Take care of parsing a number (anything that starts with a digit).
629 Set yylval and return the token type; update lexptr.
630 LEN is the number of characters in it. */
632 /*** Needs some error checking for the float case ***/
635 parse_number (struct parser_state *par_state,
636 const char *p, int len, int parsed_float, YYSTYPE *putithere)
641 int base = input_radix;
645 struct type *signed_type;
646 struct type *unsigned_type;
650 /* It's a float since it contains a point or an exponent. */
651 /* [dD] is not understood as an exponent by parse_float,
656 for (tmp2 = tmp; *tmp2; ++tmp2)
657 if (*tmp2 == 'd' || *tmp2 == 'D')
660 /* FIXME: Should this use different types? */
661 putithere->typed_val_float.type = parse_f_type (pstate)->builtin_real_s8;
662 bool parsed = parse_float (tmp, len,
663 putithere->typed_val_float.type,
664 putithere->typed_val_float.val);
666 return parsed? FLOAT : ERROR;
669 /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
705 if (len == 0 && c == 'l')
707 else if (len == 0 && c == 'u')
712 if (c >= '0' && c <= '9')
714 else if (c >= 'a' && c <= 'f')
717 return ERROR; /* Char not a digit */
719 return ERROR; /* Invalid digit in this base */
723 /* Portably test for overflow (only works for nonzero values, so make
724 a second check for zero). */
725 if ((prevn >= n) && n != 0)
726 unsigned_p=1; /* Try something unsigned */
727 /* If range checking enabled, portably test for unsigned overflow. */
728 if (RANGE_CHECK && n != 0)
730 if ((unsigned_p && (unsigned)prevn >= (unsigned)n))
731 range_error (_("Overflow on numeric constant."));
736 /* If the number is too big to be an int, or it's got an l suffix
737 then it's a long. Work out if this has to be a long by
738 shifting right and seeing if anything remains, and the
739 target int size is different to the target long size.
741 In the expression below, we could have tested
742 (n >> gdbarch_int_bit (parse_gdbarch))
743 to see if it was zero,
744 but too many compilers warn about that, when ints and longs
745 are the same size. So we shift it twice, with fewer bits
746 each time, for the same result. */
748 if ((gdbarch_int_bit (parse_gdbarch (par_state))
749 != gdbarch_long_bit (parse_gdbarch (par_state))
751 >> (gdbarch_int_bit (parse_gdbarch (par_state))-2))) /* Avoid
755 high_bit = ((ULONGEST)1)
756 << (gdbarch_long_bit (parse_gdbarch (par_state))-1);
757 unsigned_type = parse_type (par_state)->builtin_unsigned_long;
758 signed_type = parse_type (par_state)->builtin_long;
763 ((ULONGEST)1) << (gdbarch_int_bit (parse_gdbarch (par_state)) - 1);
764 unsigned_type = parse_type (par_state)->builtin_unsigned_int;
765 signed_type = parse_type (par_state)->builtin_int;
768 putithere->typed_val.val = n;
770 /* If the high bit of the worked out type is set then this number
771 has to be unsigned. */
773 if (unsigned_p || (n & high_bit))
774 putithere->typed_val.type = unsigned_type;
776 putithere->typed_val.type = signed_type;
785 enum exp_opcode opcode;
788 static const struct token dot_ops[] =
790 { ".and.", BOOL_AND, BINOP_END },
791 { ".AND.", BOOL_AND, BINOP_END },
792 { ".or.", BOOL_OR, BINOP_END },
793 { ".OR.", BOOL_OR, BINOP_END },
794 { ".not.", BOOL_NOT, BINOP_END },
795 { ".NOT.", BOOL_NOT, BINOP_END },
796 { ".eq.", EQUAL, BINOP_END },
797 { ".EQ.", EQUAL, BINOP_END },
798 { ".eqv.", EQUAL, BINOP_END },
799 { ".NEQV.", NOTEQUAL, BINOP_END },
800 { ".neqv.", NOTEQUAL, BINOP_END },
801 { ".EQV.", EQUAL, BINOP_END },
802 { ".ne.", NOTEQUAL, BINOP_END },
803 { ".NE.", NOTEQUAL, BINOP_END },
804 { ".le.", LEQ, BINOP_END },
805 { ".LE.", LEQ, BINOP_END },
806 { ".ge.", GEQ, BINOP_END },
807 { ".GE.", GEQ, BINOP_END },
808 { ".gt.", GREATERTHAN, BINOP_END },
809 { ".GT.", GREATERTHAN, BINOP_END },
810 { ".lt.", LESSTHAN, BINOP_END },
811 { ".LT.", LESSTHAN, BINOP_END },
812 { NULL, 0, BINOP_END }
815 struct f77_boolean_val
821 static const struct f77_boolean_val boolean_values[] =
830 static const struct token f77_keywords[] =
832 { "complex_16", COMPLEX_S16_KEYWORD, BINOP_END },
833 { "complex_32", COMPLEX_S32_KEYWORD, BINOP_END },
834 { "character", CHARACTER, BINOP_END },
835 { "integer_2", INT_S2_KEYWORD, BINOP_END },
836 { "logical_1", LOGICAL_S1_KEYWORD, BINOP_END },
837 { "logical_2", LOGICAL_S2_KEYWORD, BINOP_END },
838 { "logical_8", LOGICAL_S8_KEYWORD, BINOP_END },
839 { "complex_8", COMPLEX_S8_KEYWORD, BINOP_END },
840 { "integer", INT_KEYWORD, BINOP_END },
841 { "logical", LOGICAL_KEYWORD, BINOP_END },
842 { "real_16", REAL_S16_KEYWORD, BINOP_END },
843 { "complex", COMPLEX_S8_KEYWORD, BINOP_END },
844 { "sizeof", SIZEOF, BINOP_END },
845 { "real_8", REAL_S8_KEYWORD, BINOP_END },
846 { "real", REAL_KEYWORD, BINOP_END },
847 { NULL, 0, BINOP_END }
850 /* Implementation of a dynamically expandable buffer for processing input
851 characters acquired through lexptr and building a value to return in
852 yylval. Ripped off from ch-exp.y */
854 static char *tempbuf; /* Current buffer contents */
855 static int tempbufsize; /* Size of allocated buffer */
856 static int tempbufindex; /* Current index into buffer */
858 #define GROWBY_MIN_SIZE 64 /* Minimum amount to grow buffer by */
860 #define CHECKBUF(size) \
862 if (tempbufindex + (size) >= tempbufsize) \
864 growbuf_by_size (size); \
869 /* Grow the static temp buffer if necessary, including allocating the
870 first one on demand. */
873 growbuf_by_size (int count)
877 growby = std::max (count, GROWBY_MIN_SIZE);
878 tempbufsize += growby;
880 tempbuf = (char *) malloc (tempbufsize);
882 tempbuf = (char *) realloc (tempbuf, tempbufsize);
885 /* Blatantly ripped off from ch-exp.y. This routine recognizes F77
888 Recognize a string literal. A string literal is a nonzero sequence
889 of characters enclosed in matching single quotes, except that
890 a single character inside single quotes is a character literal, which
891 we reject as a string literal. To embed the terminator character inside
892 a string, it is simply doubled (I.E. 'this''is''one''string') */
895 match_string_literal (void)
897 const char *tokptr = lexptr;
899 for (tempbufindex = 0, tokptr++; *tokptr != '\0'; tokptr++)
902 if (*tokptr == *lexptr)
904 if (*(tokptr + 1) == *lexptr)
909 tempbuf[tempbufindex++] = *tokptr;
911 if (*tokptr == '\0' /* no terminator */
912 || tempbufindex == 0) /* no string */
916 tempbuf[tempbufindex] = '\0';
917 yylval.sval.ptr = tempbuf;
918 yylval.sval.length = tempbufindex;
920 return STRING_LITERAL;
924 /* Read one token, getting characters through lexptr. */
931 unsigned int i,token;
932 const char *tokstart;
936 prev_lexptr = lexptr;
940 /* First of all, let us make sure we are not dealing with the
941 special tokens .true. and .false. which evaluate to 1 and 0. */
945 for (i = 0; boolean_values[i].name != NULL; i++)
947 if (strncmp (tokstart, boolean_values[i].name,
948 strlen (boolean_values[i].name)) == 0)
950 lexptr += strlen (boolean_values[i].name);
951 yylval.lval = boolean_values[i].value;
952 return BOOLEAN_LITERAL;
957 /* See if it is a special .foo. operator. */
959 for (i = 0; dot_ops[i].oper != NULL; i++)
960 if (strncmp (tokstart, dot_ops[i].oper,
961 strlen (dot_ops[i].oper)) == 0)
963 lexptr += strlen (dot_ops[i].oper);
964 yylval.opcode = dot_ops[i].opcode;
965 return dot_ops[i].token;
968 /* See if it is an exponentiation operator. */
970 if (strncmp (tokstart, "**", 2) == 0)
973 yylval.opcode = BINOP_EXP;
977 switch (c = *tokstart)
989 token = match_string_literal ();
1000 if (paren_depth == 0)
1007 if (comma_terminates && paren_depth == 0)
1013 /* Might be a floating point number. */
1014 if (lexptr[1] < '0' || lexptr[1] > '9')
1015 goto symbol; /* Nope, must be a symbol. */
1016 /* FALL THRU into number case. */
1029 /* It's a number. */
1030 int got_dot = 0, got_e = 0, got_d = 0, toktype;
1031 const char *p = tokstart;
1032 int hex = input_radix > 10;
1034 if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1039 else if (c == '0' && (p[1]=='t' || p[1]=='T'
1040 || p[1]=='d' || p[1]=='D'))
1048 if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1049 got_dot = got_e = 1;
1050 else if (!hex && !got_d && (*p == 'd' || *p == 'D'))
1051 got_dot = got_d = 1;
1052 else if (!hex && !got_dot && *p == '.')
1054 else if (((got_e && (p[-1] == 'e' || p[-1] == 'E'))
1055 || (got_d && (p[-1] == 'd' || p[-1] == 'D')))
1056 && (*p == '-' || *p == '+'))
1057 /* This is the sign of the exponent, not the end of the
1060 /* We will take any letters or digits. parse_number will
1061 complain if past the radix, or if L or U are not final. */
1062 else if ((*p < '0' || *p > '9')
1063 && ((*p < 'a' || *p > 'z')
1064 && (*p < 'A' || *p > 'Z')))
1067 toktype = parse_number (pstate, tokstart, p - tokstart,
1068 got_dot|got_e|got_d,
1070 if (toktype == ERROR)
1072 char *err_copy = (char *) alloca (p - tokstart + 1);
1074 memcpy (err_copy, tokstart, p - tokstart);
1075 err_copy[p - tokstart] = 0;
1076 error (_("Invalid number \"%s\"."), err_copy);
1107 if (!(c == '_' || c == '$' || c ==':'
1108 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1109 /* We must have come across a bad character (e.g. ';'). */
1110 error (_("Invalid character '%c' in expression."), c);
1113 for (c = tokstart[namelen];
1114 (c == '_' || c == '$' || c == ':' || (c >= '0' && c <= '9')
1115 || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));
1116 c = tokstart[++namelen]);
1118 /* The token "if" terminates the expression and is NOT
1119 removed from the input stream. */
1121 if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1126 /* Catch specific keywords. */
1128 for (i = 0; f77_keywords[i].oper != NULL; i++)
1129 if (strlen (f77_keywords[i].oper) == namelen
1130 && strncmp (tokstart, f77_keywords[i].oper, namelen) == 0)
1132 /* lexptr += strlen(f77_keywords[i].operator); */
1133 yylval.opcode = f77_keywords[i].opcode;
1134 return f77_keywords[i].token;
1137 yylval.sval.ptr = tokstart;
1138 yylval.sval.length = namelen;
1140 if (*tokstart == '$')
1142 write_dollar_variable (pstate, yylval.sval);
1146 /* Use token-type TYPENAME for symbols that happen to be defined
1147 currently as names of types; NAME for other symbols.
1148 The caller is not constrained to care about the distinction. */
1150 char *tmp = copy_name (yylval.sval);
1151 struct block_symbol result;
1152 struct field_of_this_result is_a_field_of_this;
1153 enum domain_enum_tag lookup_domains[] =
1162 for (i = 0; i < ARRAY_SIZE (lookup_domains); ++i)
1164 /* Initialize this in case we *don't* use it in this call; that
1165 way we can refer to it unconditionally below. */
1166 memset (&is_a_field_of_this, 0, sizeof (is_a_field_of_this));
1168 result = lookup_symbol (tmp, expression_context_block,
1170 parse_language (pstate)->la_language
1172 ? &is_a_field_of_this : NULL);
1173 if (result.symbol && SYMBOL_CLASS (result.symbol) == LOC_TYPEDEF)
1175 yylval.tsym.type = SYMBOL_TYPE (result.symbol);
1184 = language_lookup_primitive_type (parse_language (pstate),
1185 parse_gdbarch (pstate), tmp);
1186 if (yylval.tsym.type != NULL)
1189 /* Input names that aren't symbols but ARE valid hex numbers,
1190 when the input radix permits them, can be names or numbers
1191 depending on the parse. Note we support radixes > 16 here. */
1193 && ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1194 || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1196 YYSTYPE newlval; /* Its value is ignored. */
1197 hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1200 yylval.ssym.sym = result;
1201 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1206 /* Any other kind of symbol */
1207 yylval.ssym.sym = result;
1208 yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1214 f_parse (struct parser_state *par_state)
1216 /* Setting up the parser state. */
1217 scoped_restore pstate_restore = make_scoped_restore (&pstate);
1218 gdb_assert (par_state != NULL);
1225 yyerror (const char *msg)
1228 lexptr = prev_lexptr;
1230 error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);