Replace the block_found global with explicit data-flow
[external/binutils.git] / gdb / d-exp.y
1 /* YACC parser for D expressions, for GDB.
2
3    Copyright (C) 2014-2015 Free Software Foundation, Inc.
4
5    This file is part of GDB.
6
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.
11
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.
16
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/>.  */
19
20 /* This file is derived from c-exp.y, jv-exp.y.  */
21
22 /* Parse a D expression from text in a string,
23    and return the result as a struct expression pointer.
24    That structure contains arithmetic operations in reverse polish,
25    with constants represented by operations that are followed by special data.
26    See expression.h for the details of the format.
27    What is important here is that it can be built up sequentially
28    during the process of parsing; the lower levels of the tree always
29    come first in the result.
30
31    Note that malloc's and realloc's in this file are transformed to
32    xmalloc and xrealloc respectively by the same sed command in the
33    makefile that remaps any other malloc/realloc inserted by the parser
34    generator.  Doing this with #defines and trying to control the interaction
35    with include files (<malloc.h> and <stdlib.h> for example) just became
36    too messy, particularly when such includes can be inserted at random
37    times by the parser generator.  */
38
39 %{
40
41 #include "defs.h"
42 #include <ctype.h>
43 #include "expression.h"
44 #include "value.h"
45 #include "parser-defs.h"
46 #include "language.h"
47 #include "c-lang.h"
48 #include "d-lang.h"
49 #include "bfd.h" /* Required by objfiles.h.  */
50 #include "symfile.h" /* Required by objfiles.h.  */
51 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
52 #include "charset.h"
53 #include "block.h"
54
55 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
56 #define parse_d_type(ps) builtin_d_type (parse_gdbarch (ps))
57
58 /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
59    as well as gratuitiously global symbol names, so we can have multiple
60    yacc generated parsers in gdb.  Note that these are only the variables
61    produced by yacc.  If other parser generators (bison, byacc, etc) produce
62    additional global names that conflict at link time, then those parser
63    generators need to be fixed instead of adding those names to this list.  */
64
65 #define yymaxdepth d_maxdepth
66 #define yyparse d_parse_internal
67 #define yylex   d_lex
68 #define yyerror d_error
69 #define yylval  d_lval
70 #define yychar  d_char
71 #define yydebug d_debug
72 #define yypact  d_pact
73 #define yyr1    d_r1
74 #define yyr2    d_r2
75 #define yydef   d_def
76 #define yychk   d_chk
77 #define yypgo   d_pgo
78 #define yyact   d_act
79 #define yyexca  d_exca
80 #define yyerrflag d_errflag
81 #define yynerrs d_nerrs
82 #define yyps    d_ps
83 #define yypv    d_pv
84 #define yys     d_s
85 #define yy_yys  d_yys
86 #define yystate d_state
87 #define yytmp   d_tmp
88 #define yyv     d_v
89 #define yy_yyv  d_yyv
90 #define yyval   d_val
91 #define yylloc  d_lloc
92 #define yyreds  d_reds  /* With YYDEBUG defined */
93 #define yytoks  d_toks  /* With YYDEBUG defined */
94 #define yyname  d_name  /* With YYDEBUG defined */
95 #define yyrule  d_rule  /* With YYDEBUG defined */
96 #define yylhs   d_yylhs
97 #define yylen   d_yylen
98 #define yydefre d_yydefred
99 #define yydgoto d_yydgoto
100 #define yysindex d_yysindex
101 #define yyrindex d_yyrindex
102 #define yygindex d_yygindex
103 #define yytable d_yytable
104 #define yycheck d_yycheck
105 #define yyss    d_yyss
106 #define yysslim d_yysslim
107 #define yyssp   d_yyssp
108 #define yystacksize d_yystacksize
109 #define yyvs    d_yyvs
110 #define yyvsp   d_yyvsp
111
112 #ifndef YYDEBUG
113 #define YYDEBUG 1       /* Default to yydebug support */
114 #endif
115
116 #define YYFPRINTF parser_fprintf
117
118 /* The state of the parser, used internally when we are parsing the
119    expression.  */
120
121 static struct parser_state *pstate = NULL;
122
123 int yyparse (void);
124
125 static int yylex (void);
126
127 void yyerror (char *);
128
129 %}
130
131 /* Although the yacc "value" of an expression is not used,
132    since the result is stored in the structure being created,
133    other node types do have values.  */
134
135 %union
136   {
137     struct {
138       LONGEST val;
139       struct type *type;
140     } typed_val_int;
141     struct {
142       DOUBLEST dval;
143       struct type *type;
144     } typed_val_float;
145     struct symbol *sym;
146     struct type *tval;
147     struct typed_stoken tsval;
148     struct stoken sval;
149     struct ttype tsym;
150     struct symtoken ssym;
151     int ival;
152     struct block *bval;
153     enum exp_opcode opcode;
154     struct stoken_vector svec;
155   }
156
157 %{
158 /* YYSTYPE gets defined by %union */
159 static int parse_number (struct parser_state *, const char *,
160                          int, int, YYSTYPE *);
161
162 static void push_expression_name (struct parser_state *, struct stoken);
163 %}
164
165 %token <sval> IDENTIFIER
166 %token <tsym> TYPENAME
167 %token <voidval> COMPLETE
168
169 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
170    but which would parse as a valid number in the current input radix.
171    E.g. "c" when input_radix==16.  Depending on the parse, it will be
172    turned into a name or into a number.  */
173
174 %token <sval> NAME_OR_INT
175
176 %token <typed_val_int> INTEGER_LITERAL
177 %token <typed_val_float> FLOAT_LITERAL
178 %token <tsval> CHARACTER_LITERAL
179 %token <tsval> STRING_LITERAL
180
181 %type <svec> StringExp
182 %type <tval> BasicType TypeExp
183 %type <sval> IdentifierExp
184 %type <ival> ArrayLiteral
185
186 %token ENTRY
187 %token ERROR
188
189 /* Keywords that have a constant value.  */
190 %token TRUE_KEYWORD FALSE_KEYWORD NULL_KEYWORD
191 /* Class 'super' accessor.  */
192 %token SUPER_KEYWORD
193 /* Properties.  */
194 %token CAST_KEYWORD SIZEOF_KEYWORD
195 %token TYPEOF_KEYWORD TYPEID_KEYWORD
196 %token INIT_KEYWORD
197 /* Comparison keywords.  */
198 /* Type storage classes.  */
199 %token IMMUTABLE_KEYWORD CONST_KEYWORD SHARED_KEYWORD
200 /* Non-scalar type keywords.  */
201 %token STRUCT_KEYWORD UNION_KEYWORD
202 %token CLASS_KEYWORD INTERFACE_KEYWORD
203 %token ENUM_KEYWORD TEMPLATE_KEYWORD
204 %token DELEGATE_KEYWORD FUNCTION_KEYWORD
205
206 %token <sval> DOLLAR_VARIABLE
207
208 %token <opcode> ASSIGN_MODIFY
209
210 %left ','
211 %right '=' ASSIGN_MODIFY
212 %right '?'
213 %left OROR
214 %left ANDAND
215 %left '|'
216 %left '^'
217 %left '&'
218 %left EQUAL NOTEQUAL '<' '>' LEQ GEQ
219 %right LSH RSH
220 %left '+' '-'
221 %left '*' '/' '%'
222 %right HATHAT
223 %left IDENTITY NOTIDENTITY
224 %right INCREMENT DECREMENT
225 %right '.' '[' '('
226 %token DOTDOT
227
228 \f
229 %%
230
231 start   :
232         Expression
233 |       TypeExp
234 ;
235
236 /* Expressions, including the comma operator.  */
237
238 Expression:
239         CommaExpression
240 ;
241
242 CommaExpression:
243         AssignExpression
244 |       AssignExpression ',' CommaExpression
245                 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
246 ;
247
248 AssignExpression:
249         ConditionalExpression
250 |       ConditionalExpression '=' AssignExpression
251                 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
252 |       ConditionalExpression ASSIGN_MODIFY AssignExpression
253                 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
254                   write_exp_elt_opcode (pstate, $2);
255                   write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
256 ;
257
258 ConditionalExpression:
259         OrOrExpression
260 |       OrOrExpression '?' Expression ':' ConditionalExpression
261                 { write_exp_elt_opcode (pstate, TERNOP_COND); }
262 ;
263
264 OrOrExpression:
265         AndAndExpression
266 |       OrOrExpression OROR AndAndExpression
267                 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
268 ;
269
270 AndAndExpression:
271         OrExpression
272 |       AndAndExpression ANDAND OrExpression
273                 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
274 ;
275
276 OrExpression:
277         XorExpression
278 |       OrExpression '|' XorExpression
279                 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
280 ;
281
282 XorExpression:
283         AndExpression
284 |       XorExpression '^' AndExpression
285                 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
286 ;
287
288 AndExpression:
289         CmpExpression
290 |       AndExpression '&' CmpExpression
291                 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
292 ;
293
294 CmpExpression:
295         ShiftExpression
296 |       EqualExpression
297 |       IdentityExpression
298 |       RelExpression
299 ;
300
301 EqualExpression:
302         ShiftExpression EQUAL ShiftExpression
303                 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
304 |       ShiftExpression NOTEQUAL ShiftExpression
305                 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
306 ;
307
308 IdentityExpression:
309         ShiftExpression IDENTITY ShiftExpression
310                 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
311 |       ShiftExpression NOTIDENTITY ShiftExpression
312                 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
313 ;
314
315 RelExpression:
316         ShiftExpression '<' ShiftExpression
317                 { write_exp_elt_opcode (pstate, BINOP_LESS); }
318 |       ShiftExpression LEQ ShiftExpression
319                 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
320 |       ShiftExpression '>' ShiftExpression
321                 { write_exp_elt_opcode (pstate, BINOP_GTR); }
322 |       ShiftExpression GEQ ShiftExpression
323                 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
324 ;
325
326 ShiftExpression:
327         AddExpression
328 |       ShiftExpression LSH AddExpression
329                 { write_exp_elt_opcode (pstate, BINOP_LSH); }
330 |       ShiftExpression RSH AddExpression
331                 { write_exp_elt_opcode (pstate, BINOP_RSH); }
332 ;
333
334 AddExpression:
335         MulExpression
336 |       AddExpression '+' MulExpression
337                 { write_exp_elt_opcode (pstate, BINOP_ADD); }
338 |       AddExpression '-' MulExpression
339                 { write_exp_elt_opcode (pstate, BINOP_SUB); }
340 |       AddExpression '~' MulExpression
341                 { write_exp_elt_opcode (pstate, BINOP_CONCAT); }
342 ;
343
344 MulExpression:
345         UnaryExpression
346 |       MulExpression '*' UnaryExpression
347                 { write_exp_elt_opcode (pstate, BINOP_MUL); }
348 |       MulExpression '/' UnaryExpression
349                 { write_exp_elt_opcode (pstate, BINOP_DIV); }
350 |       MulExpression '%' UnaryExpression
351                 { write_exp_elt_opcode (pstate, BINOP_REM); }
352
353 UnaryExpression:
354         '&' UnaryExpression
355                 { write_exp_elt_opcode (pstate, UNOP_ADDR); }
356 |       INCREMENT UnaryExpression
357                 { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
358 |       DECREMENT UnaryExpression
359                 { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
360 |       '*' UnaryExpression
361                 { write_exp_elt_opcode (pstate, UNOP_IND); }
362 |       '-' UnaryExpression
363                 { write_exp_elt_opcode (pstate, UNOP_NEG); }
364 |       '+' UnaryExpression
365                 { write_exp_elt_opcode (pstate, UNOP_PLUS); }
366 |       '!' UnaryExpression
367                 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
368 |       '~' UnaryExpression
369                 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
370 |       CastExpression
371 |       PowExpression
372 ;
373
374 CastExpression:
375         CAST_KEYWORD '(' TypeExp ')' UnaryExpression
376                 { write_exp_elt_opcode (pstate, UNOP_CAST);
377                   write_exp_elt_type (pstate, $3);
378                   write_exp_elt_opcode (pstate, UNOP_CAST); }
379         /* C style cast is illegal D, but is still recognised in
380            the grammar, so we keep this around for convenience.  */
381 |       '(' TypeExp ')' UnaryExpression
382                 { write_exp_elt_opcode (pstate, UNOP_CAST);
383                   write_exp_elt_type (pstate, $2);
384                   write_exp_elt_opcode (pstate, UNOP_CAST); }
385 ;
386
387 PowExpression:
388         PostfixExpression
389 |       PostfixExpression HATHAT UnaryExpression
390                 { write_exp_elt_opcode (pstate, BINOP_EXP); }
391 ;
392
393 PostfixExpression:
394         PrimaryExpression
395 |       PostfixExpression INCREMENT
396                 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
397 |       PostfixExpression DECREMENT
398                 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
399 |       CallExpression
400 |       IndexExpression
401 |       SliceExpression
402 ;
403
404 ArgumentList:
405         AssignExpression
406                 { arglist_len = 1; }
407 |       ArgumentList ',' AssignExpression
408                 { arglist_len++; }
409 ;
410
411 ArgumentList_opt:
412         /* EMPTY */
413                 { arglist_len = 0; }
414 |       ArgumentList
415 ;
416
417 CallExpression:
418         PostfixExpression '('
419                 { start_arglist (); }
420         ArgumentList_opt ')'
421                 { write_exp_elt_opcode (pstate, OP_FUNCALL);
422                   write_exp_elt_longcst (pstate, (LONGEST) end_arglist ());
423                   write_exp_elt_opcode (pstate, OP_FUNCALL); }
424 ;
425
426 IndexExpression:
427         PostfixExpression '[' ArgumentList ']'
428                 { if (arglist_len > 0)
429                     {
430                       write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
431                       write_exp_elt_longcst (pstate, (LONGEST) arglist_len);
432                       write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
433                     }
434                   else
435                     write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
436                 }
437 ;
438
439 SliceExpression:
440         PostfixExpression '[' ']'
441                 { /* Do nothing.  */ }
442 |       PostfixExpression '[' AssignExpression DOTDOT AssignExpression ']'
443                 { write_exp_elt_opcode (pstate, TERNOP_SLICE); }
444 ;
445
446 PrimaryExpression:
447         '(' Expression ')'
448                 { /* Do nothing.  */ }
449 |       IdentifierExp
450                 { push_expression_name (pstate, $1); }
451 |       IdentifierExp '.' COMPLETE
452                 { struct stoken s;
453                   s.ptr = "";
454                   s.length = 0;
455                   push_expression_name (pstate, $1);
456                   mark_struct_expression (pstate);
457                   write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
458                   write_exp_string (pstate, s);
459                   write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
460 |       IdentifierExp '.' IDENTIFIER COMPLETE
461                 { push_expression_name (pstate, $1);
462                   mark_struct_expression (pstate);
463                   write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
464                   write_exp_string (pstate, $3);
465                   write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
466 |       DOLLAR_VARIABLE
467                 { write_dollar_variable (pstate, $1); }
468 |       NAME_OR_INT
469                 { YYSTYPE val;
470                   parse_number (pstate, $1.ptr, $1.length, 0, &val);
471                   write_exp_elt_opcode (pstate, OP_LONG);
472                   write_exp_elt_type (pstate, val.typed_val_int.type);
473                   write_exp_elt_longcst (pstate,
474                                          (LONGEST) val.typed_val_int.val);
475                   write_exp_elt_opcode (pstate, OP_LONG); }
476 |       NULL_KEYWORD
477                 { struct type *type = parse_d_type (pstate)->builtin_void;
478                   type = lookup_pointer_type (type);
479                   write_exp_elt_opcode (pstate, OP_LONG);
480                   write_exp_elt_type (pstate, type);
481                   write_exp_elt_longcst (pstate, (LONGEST) 0);
482                   write_exp_elt_opcode (pstate, OP_LONG); }
483 |       TRUE_KEYWORD
484                 { write_exp_elt_opcode (pstate, OP_BOOL);
485                   write_exp_elt_longcst (pstate, (LONGEST) 1);
486                   write_exp_elt_opcode (pstate, OP_BOOL); }
487 |       FALSE_KEYWORD
488                 { write_exp_elt_opcode (pstate, OP_BOOL);
489                   write_exp_elt_longcst (pstate, (LONGEST) 0);
490                   write_exp_elt_opcode (pstate, OP_BOOL); }
491 |       INTEGER_LITERAL
492                 { write_exp_elt_opcode (pstate, OP_LONG);
493                   write_exp_elt_type (pstate, $1.type);
494                   write_exp_elt_longcst (pstate, (LONGEST)($1.val));
495                   write_exp_elt_opcode (pstate, OP_LONG); }
496 |       FLOAT_LITERAL
497                 { write_exp_elt_opcode (pstate, OP_DOUBLE);
498                   write_exp_elt_type (pstate, $1.type);
499                   write_exp_elt_dblcst (pstate, $1.dval);
500                   write_exp_elt_opcode (pstate, OP_DOUBLE); }
501 |       CHARACTER_LITERAL
502                 { struct stoken_vector vec;
503                   vec.len = 1;
504                   vec.tokens = &$1;
505                   write_exp_string_vector (pstate, $1.type, &vec); }
506 |       StringExp
507                 { int i;
508                   write_exp_string_vector (pstate, 0, &$1);
509                   for (i = 0; i < $1.len; ++i)
510                     free ($1.tokens[i].ptr);
511                   free ($1.tokens); }
512 |       ArrayLiteral
513                 { write_exp_elt_opcode (pstate, OP_ARRAY);
514                   write_exp_elt_longcst (pstate, (LONGEST) 0);
515                   write_exp_elt_longcst (pstate, (LONGEST) $1 - 1);
516                   write_exp_elt_opcode (pstate, OP_ARRAY); }
517 ;
518
519 ArrayLiteral:
520         '[' ArgumentList_opt ']'
521                 { $$ = arglist_len; }
522 ;
523
524 IdentifierExp:
525         IDENTIFIER
526 |       IdentifierExp '.' IDENTIFIER
527                 { $$.length = $1.length + $3.length + 1;
528                   if ($1.ptr + $1.length + 1 == $3.ptr
529                       && $1.ptr[$1.length] == '.')
530                     $$.ptr = $1.ptr;  /* Optimization.  */
531                   else
532                     {
533                       char *buf = malloc ($$.length + 1);
534                       make_cleanup (free, buf);
535                       sprintf (buf, "%.*s.%.*s",
536                                $1.length, $1.ptr, $3.length, $3.ptr);
537                       $$.ptr = buf;
538                     }
539                 }
540 ;
541
542 StringExp:
543         STRING_LITERAL
544                 { /* We copy the string here, and not in the
545                      lexer, to guarantee that we do not leak a
546                      string.  Note that we follow the
547                      NUL-termination convention of the
548                      lexer.  */
549                   struct typed_stoken *vec = XNEW (struct typed_stoken);
550                   $$.len = 1;
551                   $$.tokens = vec;
552
553                   vec->type = $1.type;
554                   vec->length = $1.length;
555                   vec->ptr = malloc ($1.length + 1);
556                   memcpy (vec->ptr, $1.ptr, $1.length + 1);
557                 }
558 |       StringExp STRING_LITERAL
559                 { /* Note that we NUL-terminate here, but just
560                      for convenience.  */
561                   char *p;
562                   ++$$.len;
563                   $$.tokens = realloc ($$.tokens,
564                                        $$.len * sizeof (struct typed_stoken));
565
566                   p = malloc ($2.length + 1);
567                   memcpy (p, $2.ptr, $2.length + 1);
568
569                   $$.tokens[$$.len - 1].type = $2.type;
570                   $$.tokens[$$.len - 1].length = $2.length;
571                   $$.tokens[$$.len - 1].ptr = p;
572                 }
573 ;
574
575 TypeExp:
576         BasicType
577                 { write_exp_elt_opcode (pstate, OP_TYPE);
578                   write_exp_elt_type (pstate, $1);
579                   write_exp_elt_opcode (pstate, OP_TYPE); }
580 |       BasicType BasicType2
581                 { $$ = follow_types ($1);
582                   write_exp_elt_opcode (pstate, OP_TYPE);
583                   write_exp_elt_type (pstate, $$);
584                   write_exp_elt_opcode (pstate, OP_TYPE);
585                 }
586 ;
587
588 BasicType2:
589         '*'
590                 { push_type (tp_pointer); }
591 |       '*' BasicType2
592                 { push_type (tp_pointer); }
593 |       '[' INTEGER_LITERAL ']'
594                 { push_type_int ($2.val);
595                   push_type (tp_array); }
596 |       '[' INTEGER_LITERAL ']' BasicType2
597                 { push_type_int ($2.val);
598                   push_type (tp_array); }
599 ;
600
601 BasicType:
602         TYPENAME
603                 { $$ = $1.type; }
604 |       CLASS_KEYWORD IdentifierExp
605                 { $$ = lookup_struct (copy_name ($2),
606                                       expression_context_block); }
607 |       CLASS_KEYWORD COMPLETE
608                 { mark_completion_tag (TYPE_CODE_STRUCT, "", 0);
609                   $$ = NULL; }
610 |       CLASS_KEYWORD IdentifierExp COMPLETE
611                 { mark_completion_tag (TYPE_CODE_STRUCT, $2.ptr, $2.length);
612                   $$ = NULL; }
613 |       STRUCT_KEYWORD IdentifierExp
614                 { $$ = lookup_struct (copy_name ($2),
615                                       expression_context_block); }
616 |       STRUCT_KEYWORD COMPLETE
617                 { mark_completion_tag (TYPE_CODE_STRUCT, "", 0);
618                   $$ = NULL; }
619 |       STRUCT_KEYWORD IdentifierExp COMPLETE
620                 { mark_completion_tag (TYPE_CODE_STRUCT, $2.ptr, $2.length);
621                   $$ = NULL; }
622 |       UNION_KEYWORD IdentifierExp
623                 { $$ = lookup_union (copy_name ($2),
624                                      expression_context_block); }
625 |       UNION_KEYWORD COMPLETE
626                 { mark_completion_tag (TYPE_CODE_UNION, "", 0);
627                   $$ = NULL; }
628 |       UNION_KEYWORD IdentifierExp COMPLETE
629                 { mark_completion_tag (TYPE_CODE_UNION, $2.ptr, $2.length);
630                   $$ = NULL; }
631 |       ENUM_KEYWORD IdentifierExp
632                 { $$ = lookup_enum (copy_name ($2),
633                                     expression_context_block); }
634 |       ENUM_KEYWORD COMPLETE
635                 { mark_completion_tag (TYPE_CODE_ENUM, "", 0);
636                   $$ = NULL; }
637 |       ENUM_KEYWORD IdentifierExp COMPLETE
638                 { mark_completion_tag (TYPE_CODE_ENUM, $2.ptr, $2.length);
639                   $$ = NULL; }
640 ;
641
642 %%
643
644 /* Take care of parsing a number (anything that starts with a digit).
645    Set yylval and return the token type; update lexptr.
646    LEN is the number of characters in it.  */
647
648 /*** Needs some error checking for the float case ***/
649
650 static int
651 parse_number (struct parser_state *ps, const char *p,
652               int len, int parsed_float, YYSTYPE *putithere)
653 {
654   ULONGEST n = 0;
655   ULONGEST prevn = 0;
656   ULONGEST un;
657
658   int i = 0;
659   int c;
660   int base = input_radix;
661   int unsigned_p = 0;
662   int long_p = 0;
663
664   /* We have found a "L" or "U" suffix.  */
665   int found_suffix = 0;
666
667   ULONGEST high_bit;
668   struct type *signed_type;
669   struct type *unsigned_type;
670
671   if (parsed_float)
672     {
673       const struct builtin_d_type *builtin_d_types;
674       const char *suffix;
675       int suffix_len;
676       char *s, *sp;
677
678       /* Strip out all embedded '_' before passing to parse_float.  */
679       s = (char *) alloca (len + 1);
680       sp = s;
681       while (len-- > 0)
682         {
683           if (*p != '_')
684             *sp++ = *p;
685           p++;
686         }
687       *sp = '\0';
688       len = strlen (s);
689
690       if (! parse_float (s, len, &putithere->typed_val_float.dval, &suffix))
691         return ERROR;
692
693       suffix_len = s + len - suffix;
694
695       if (suffix_len == 0)
696         {
697           putithere->typed_val_float.type
698             = parse_d_type (ps)->builtin_double;
699         }
700       else if (suffix_len == 1)
701         {
702           /* Check suffix for `f', `l', or `i' (float, real, or idouble).  */
703           if (tolower (*suffix) == 'f')
704             {
705               putithere->typed_val_float.type
706                 = parse_d_type (ps)->builtin_float;
707             }
708           else if (tolower (*suffix) == 'l')
709             {
710               putithere->typed_val_float.type
711                 = parse_d_type (ps)->builtin_real;
712             }
713           else if (tolower (*suffix) == 'i')
714             {
715               putithere->typed_val_float.type
716                 = parse_d_type (ps)->builtin_idouble;
717             }
718           else
719             return ERROR;
720         }
721       else if (suffix_len == 2)
722         {
723           /* Check suffix for `fi' or `li' (ifloat or ireal).  */
724           if (tolower (suffix[0]) == 'f' && tolower (suffix[1] == 'i'))
725             {
726               putithere->typed_val_float.type
727                 = parse_d_type (ps)->builtin_ifloat;
728             }
729           else if (tolower (suffix[0]) == 'l' && tolower (suffix[1] == 'i'))
730             {
731               putithere->typed_val_float.type
732                 = parse_d_type (ps)->builtin_ireal;
733             }
734           else
735             return ERROR;
736         }
737       else
738         return ERROR;
739
740       return FLOAT_LITERAL;
741     }
742
743   /* Handle base-switching prefixes 0x, 0b, 0 */
744   if (p[0] == '0')
745     switch (p[1])
746       {
747       case 'x':
748       case 'X':
749         if (len >= 3)
750           {
751             p += 2;
752             base = 16;
753             len -= 2;
754           }
755         break;
756
757       case 'b':
758       case 'B':
759         if (len >= 3)
760           {
761             p += 2;
762             base = 2;
763             len -= 2;
764           }
765         break;
766
767       default:
768         base = 8;
769         break;
770       }
771
772   while (len-- > 0)
773     {
774       c = *p++;
775       if (c == '_')
776         continue;       /* Ignore embedded '_'.  */
777       if (c >= 'A' && c <= 'Z')
778         c += 'a' - 'A';
779       if (c != 'l' && c != 'u')
780         n *= base;
781       if (c >= '0' && c <= '9')
782         {
783           if (found_suffix)
784             return ERROR;
785           n += i = c - '0';
786         }
787       else
788         {
789           if (base > 10 && c >= 'a' && c <= 'f')
790             {
791               if (found_suffix)
792                 return ERROR;
793               n += i = c - 'a' + 10;
794             }
795           else if (c == 'l' && long_p == 0)
796             {
797               long_p = 1;
798               found_suffix = 1;
799             }
800           else if (c == 'u' && unsigned_p == 0)
801             {
802               unsigned_p = 1;
803               found_suffix = 1;
804             }
805           else
806             return ERROR;       /* Char not a digit */
807         }
808       if (i >= base)
809         return ERROR;           /* Invalid digit in this base.  */
810       /* Portably test for integer overflow.  */
811       if (c != 'l' && c != 'u')
812         {
813           ULONGEST n2 = prevn * base;
814           if ((n2 / base != prevn) || (n2 + i < prevn))
815             error (_("Numeric constant too large."));
816         }
817       prevn = n;
818     }
819
820   /* An integer constant is an int or a long.  An L suffix forces it to
821      be long, and a U suffix forces it to be unsigned.  To figure out
822      whether it fits, we shift it right and see whether anything remains.
823      Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
824      more in one operation, because many compilers will warn about such a
825      shift (which always produces a zero result).  To deal with the case
826      where it is we just always shift the value more than once, with fewer
827      bits each time.  */
828   un = (ULONGEST) n >> 2;
829   if (long_p == 0 && (un >> 30) == 0)
830     {
831       high_bit = ((ULONGEST) 1) << 31;
832       signed_type = parse_d_type (ps)->builtin_int;
833       /* For decimal notation, keep the sign of the worked out type.  */
834       if (base == 10 && !unsigned_p)
835         unsigned_type = parse_d_type (ps)->builtin_long;
836       else
837         unsigned_type = parse_d_type (ps)->builtin_uint;
838     }
839   else
840     {
841       int shift;
842       if (sizeof (ULONGEST) * HOST_CHAR_BIT < 64)
843         /* A long long does not fit in a LONGEST.  */
844         shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
845       else
846         shift = 63;
847       high_bit = (ULONGEST) 1 << shift;
848       signed_type = parse_d_type (ps)->builtin_long;
849       unsigned_type = parse_d_type (ps)->builtin_ulong;
850     }
851
852   putithere->typed_val_int.val = n;
853
854   /* If the high bit of the worked out type is set then this number
855      has to be unsigned_type.  */
856   if (unsigned_p || (n & high_bit))
857     putithere->typed_val_int.type = unsigned_type;
858   else
859     putithere->typed_val_int.type = signed_type;
860
861   return INTEGER_LITERAL;
862 }
863
864 /* Temporary obstack used for holding strings.  */
865 static struct obstack tempbuf;
866 static int tempbuf_init;
867
868 /* Parse a string or character literal from TOKPTR.  The string or
869    character may be wide or unicode.  *OUTPTR is set to just after the
870    end of the literal in the input string.  The resulting token is
871    stored in VALUE.  This returns a token value, either STRING or
872    CHAR, depending on what was parsed.  *HOST_CHARS is set to the
873    number of host characters in the literal.  */
874
875 static int
876 parse_string_or_char (const char *tokptr, const char **outptr,
877                       struct typed_stoken *value, int *host_chars)
878 {
879   int quote;
880
881   /* Build the gdb internal form of the input string in tempbuf.  Note
882      that the buffer is null byte terminated *only* for the
883      convenience of debugging gdb itself and printing the buffer
884      contents when the buffer contains no embedded nulls.  Gdb does
885      not depend upon the buffer being null byte terminated, it uses
886      the length string instead.  This allows gdb to handle C strings
887      (as well as strings in other languages) with embedded null
888      bytes */
889
890   if (!tempbuf_init)
891     tempbuf_init = 1;
892   else
893     obstack_free (&tempbuf, NULL);
894   obstack_init (&tempbuf);
895
896   /* Skip the quote.  */
897   quote = *tokptr;
898   ++tokptr;
899
900   *host_chars = 0;
901
902   while (*tokptr)
903     {
904       char c = *tokptr;
905       if (c == '\\')
906         {
907            ++tokptr;
908            *host_chars += c_parse_escape (&tokptr, &tempbuf);
909         }
910       else if (c == quote)
911         break;
912       else
913         {
914           obstack_1grow (&tempbuf, c);
915           ++tokptr;
916           /* FIXME: this does the wrong thing with multi-byte host
917              characters.  We could use mbrlen here, but that would
918              make "set host-charset" a bit less useful.  */
919           ++*host_chars;
920         }
921     }
922
923   if (*tokptr != quote)
924     {
925       if (quote == '"' || quote == '`')
926         error (_("Unterminated string in expression."));
927       else
928         error (_("Unmatched single quote."));
929     }
930   ++tokptr;
931
932   /* FIXME: should instead use own language string_type enum
933      and handle D-specific string suffixes here. */
934   if (quote == '\'')
935     value->type = C_CHAR;
936   else
937     value->type = C_STRING;
938
939   value->ptr = obstack_base (&tempbuf);
940   value->length = obstack_object_size (&tempbuf);
941
942   *outptr = tokptr;
943
944   return quote == '\'' ? CHARACTER_LITERAL : STRING_LITERAL;
945 }
946
947 struct token
948 {
949   char *oper;
950   int token;
951   enum exp_opcode opcode;
952 };
953
954 static const struct token tokentab3[] =
955   {
956     {"^^=", ASSIGN_MODIFY, BINOP_EXP},
957     {"<<=", ASSIGN_MODIFY, BINOP_LSH},
958     {">>=", ASSIGN_MODIFY, BINOP_RSH},
959   };
960
961 static const struct token tokentab2[] =
962   {
963     {"+=", ASSIGN_MODIFY, BINOP_ADD},
964     {"-=", ASSIGN_MODIFY, BINOP_SUB},
965     {"*=", ASSIGN_MODIFY, BINOP_MUL},
966     {"/=", ASSIGN_MODIFY, BINOP_DIV},
967     {"%=", ASSIGN_MODIFY, BINOP_REM},
968     {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
969     {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
970     {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
971     {"++", INCREMENT, BINOP_END},
972     {"--", DECREMENT, BINOP_END},
973     {"&&", ANDAND, BINOP_END},
974     {"||", OROR, BINOP_END},
975     {"^^", HATHAT, BINOP_END},
976     {"<<", LSH, BINOP_END},
977     {">>", RSH, BINOP_END},
978     {"==", EQUAL, BINOP_END},
979     {"!=", NOTEQUAL, BINOP_END},
980     {"<=", LEQ, BINOP_END},
981     {">=", GEQ, BINOP_END},
982     {"..", DOTDOT, BINOP_END},
983   };
984
985 /* Identifier-like tokens.  */
986 static const struct token ident_tokens[] =
987   {
988     {"is", IDENTITY, BINOP_END},
989     {"!is", NOTIDENTITY, BINOP_END},
990
991     {"cast", CAST_KEYWORD, OP_NULL},
992     {"const", CONST_KEYWORD, OP_NULL},
993     {"immutable", IMMUTABLE_KEYWORD, OP_NULL},
994     {"shared", SHARED_KEYWORD, OP_NULL},
995     {"super", SUPER_KEYWORD, OP_NULL},
996
997     {"null", NULL_KEYWORD, OP_NULL},
998     {"true", TRUE_KEYWORD, OP_NULL},
999     {"false", FALSE_KEYWORD, OP_NULL},
1000
1001     {"init", INIT_KEYWORD, OP_NULL},
1002     {"sizeof", SIZEOF_KEYWORD, OP_NULL},
1003     {"typeof", TYPEOF_KEYWORD, OP_NULL},
1004     {"typeid", TYPEID_KEYWORD, OP_NULL},
1005
1006     {"delegate", DELEGATE_KEYWORD, OP_NULL},
1007     {"function", FUNCTION_KEYWORD, OP_NULL},
1008     {"struct", STRUCT_KEYWORD, OP_NULL},
1009     {"union", UNION_KEYWORD, OP_NULL},
1010     {"class", CLASS_KEYWORD, OP_NULL},
1011     {"interface", INTERFACE_KEYWORD, OP_NULL},
1012     {"enum", ENUM_KEYWORD, OP_NULL},
1013     {"template", TEMPLATE_KEYWORD, OP_NULL},
1014   };
1015
1016 /* If NAME is a type name in this scope, return it.  */
1017
1018 static struct type *
1019 d_type_from_name (struct stoken name)
1020 {
1021   struct symbol *sym;
1022   char *copy = copy_name (name);
1023
1024   sym = lookup_symbol (copy, expression_context_block,
1025                        STRUCT_DOMAIN, NULL).symbol;
1026   if (sym != NULL)
1027     return SYMBOL_TYPE (sym);
1028
1029   return NULL;
1030 }
1031
1032 /* If NAME is a module name in this scope, return it.  */
1033
1034 static struct type *
1035 d_module_from_name (struct stoken name)
1036 {
1037   struct symbol *sym;
1038   char *copy = copy_name (name);
1039
1040   sym = lookup_symbol (copy, expression_context_block,
1041                        MODULE_DOMAIN, NULL).symbol;
1042   if (sym != NULL)
1043     return SYMBOL_TYPE (sym);
1044
1045   return NULL;
1046 }
1047
1048 /* If NAME is a valid variable name in this scope, push it and return 1.
1049    Otherwise, return 0.  */
1050
1051 static int
1052 push_variable (struct parser_state *ps, struct stoken name)
1053 {
1054   char *copy = copy_name (name);
1055   struct field_of_this_result is_a_field_of_this;
1056   struct block_symbol sym
1057     = lookup_symbol (copy, expression_context_block, VAR_DOMAIN,
1058                      &is_a_field_of_this);
1059
1060   if (sym.symbol && SYMBOL_CLASS (sym.symbol) != LOC_TYPEDEF)
1061     {
1062       if (symbol_read_needs_frame (sym.symbol))
1063         {
1064           if (innermost_block == 0 ||
1065               contained_in (sym.block, innermost_block))
1066             innermost_block = sym.block;
1067         }
1068
1069       write_exp_elt_opcode (ps, OP_VAR_VALUE);
1070       /* We want to use the selected frame, not another more inner frame
1071          which happens to be in the same block.  */
1072       write_exp_elt_block (ps, NULL);
1073       write_exp_elt_sym (ps, sym.symbol);
1074       write_exp_elt_opcode (ps, OP_VAR_VALUE);
1075       return 1;
1076     }
1077   if (is_a_field_of_this.type != NULL)
1078     {
1079       /* It hangs off of `this'.  Must not inadvertently convert from a
1080          method call to data ref.  */
1081       if (innermost_block == 0 ||
1082           contained_in (sym.block, innermost_block))
1083         innermost_block = sym.block;
1084       write_exp_elt_opcode (ps, OP_THIS);
1085       write_exp_elt_opcode (ps, OP_THIS);
1086       write_exp_elt_opcode (ps, STRUCTOP_PTR);
1087       write_exp_string (ps, name);
1088       write_exp_elt_opcode (ps, STRUCTOP_PTR);
1089       return 1;
1090     }
1091   return 0;
1092 }
1093
1094 /* Assuming a reference expression has been pushed, emit the
1095    STRUCTOP_PTR ops to access the field named NAME.  If NAME is a
1096    qualified name (has '.'), generate a field access for each part.  */
1097
1098 static void
1099 push_fieldnames (struct parser_state *ps, struct stoken name)
1100 {
1101   int i;
1102   struct stoken token;
1103   token.ptr = name.ptr;
1104   for (i = 0;  ;  i++)
1105     {
1106       if (i == name.length || name.ptr[i] == '.')
1107         {
1108           /* token.ptr is start of current field name.  */
1109           token.length = &name.ptr[i] - token.ptr;
1110           write_exp_elt_opcode (ps, STRUCTOP_PTR);
1111           write_exp_string (ps, token);
1112           write_exp_elt_opcode (ps, STRUCTOP_PTR);
1113           token.ptr += token.length + 1;
1114         }
1115       if (i >= name.length)
1116         break;
1117     }
1118 }
1119
1120 /* Helper routine for push_expression_name.  Handle a TYPE symbol,
1121    where DOT_INDEX is the index of the first '.' if NAME is part of
1122    a qualified type.  */
1123
1124 static void
1125 push_type_name (struct parser_state *ps, struct type *type,
1126                 struct stoken name, int dot_index)
1127 {
1128   if (dot_index == name.length)
1129     {
1130       write_exp_elt_opcode (ps, OP_TYPE);
1131       write_exp_elt_type (ps, type);
1132       write_exp_elt_opcode (ps, OP_TYPE);
1133     }
1134   else
1135     {
1136       struct stoken token;
1137
1138       token.ptr = name.ptr;
1139       token.length = dot_index;
1140
1141       dot_index = 0;
1142
1143       while (dot_index < name.length && name.ptr[dot_index] != '.')
1144         dot_index++;
1145       token.ptr = name.ptr;
1146       token.length = dot_index;
1147
1148       write_exp_elt_opcode (ps, OP_SCOPE);
1149       write_exp_elt_type (ps, type);
1150       write_exp_string (ps, token);
1151       write_exp_elt_opcode (ps, OP_SCOPE);
1152
1153       if (dot_index < name.length)
1154         {
1155           dot_index++;
1156           name.ptr += dot_index;
1157           name.length -= dot_index;
1158           push_fieldnames (ps, name);
1159         }
1160     }
1161 }
1162
1163 /* Helper routine for push_expression_name.  Like push_type_name,
1164    but used when TYPE is a module.  Returns 1 on pushing the symbol.  */
1165
1166 static int
1167 push_module_name (struct parser_state *ps, struct type *module,
1168                   struct stoken name, int dot_index)
1169 {
1170   if (dot_index == name.length)
1171     {
1172       write_exp_elt_opcode (ps, OP_TYPE);
1173       write_exp_elt_type (ps, module);
1174       write_exp_elt_opcode (ps, OP_TYPE);
1175       return 1;
1176     }
1177   else
1178     {
1179       struct symbol *sym;
1180       char *copy;
1181
1182       copy = copy_name (name);
1183       sym = lookup_symbol_in_static_block (copy, expression_context_block,
1184                                            VAR_DOMAIN).symbol;
1185       if (sym != NULL)
1186         sym = lookup_global_symbol (copy, expression_context_block,
1187                                     VAR_DOMAIN).symbol;
1188
1189       if (sym != NULL)
1190         {
1191           if (SYMBOL_CLASS (sym) != LOC_TYPEDEF)
1192             {
1193               write_exp_elt_opcode (ps, OP_VAR_VALUE);
1194               write_exp_elt_block (ps, NULL);
1195               write_exp_elt_sym (ps, sym);
1196               write_exp_elt_opcode (ps, OP_VAR_VALUE);
1197             }
1198           else
1199             {
1200               write_exp_elt_opcode (ps, OP_TYPE);
1201               write_exp_elt_type (ps, SYMBOL_TYPE (sym));
1202               write_exp_elt_opcode (ps, OP_TYPE);
1203             }
1204           return 1;
1205         }
1206     }
1207
1208   return 0;
1209 }
1210
1211 /* Handle NAME in an expression (or LHS), which could be a
1212    variable, type, or module.  */
1213
1214 static void
1215 push_expression_name (struct parser_state *ps, struct stoken name)
1216 {
1217   struct stoken token;
1218   struct type *typ;
1219   struct bound_minimal_symbol msymbol;
1220   char *copy;
1221   int doti;
1222
1223   /* Handle VAR, which could be local or global.  */
1224   if (push_variable (ps, name) != 0)
1225     return;
1226
1227   /* Handle MODULE.  */
1228   typ = d_module_from_name (name);
1229   if (typ != NULL)
1230     {
1231       if (push_module_name (ps, typ, name, name.length) != 0)
1232         return;
1233     }
1234
1235   /* Handle TYPE.  */
1236   typ = d_type_from_name (name);
1237   if (typ != NULL)
1238     {
1239       push_type_name (ps, typ, name, name.length);
1240       return;
1241     }
1242
1243   /* Handle VAR.FIELD1..FIELDN.  */
1244   for (doti = 0;  doti < name.length;  doti++)
1245     {
1246       if (name.ptr[doti] == '.')
1247         {
1248           token.ptr = name.ptr;
1249           token.length = doti;
1250
1251           if (push_variable (ps, token) != 0)
1252             {
1253               token.ptr = name.ptr + doti + 1;
1254               token.length = name.length - doti - 1;
1255               push_fieldnames (ps, token);
1256               return;
1257             }
1258           break;
1259         }
1260     }
1261
1262   /* Continue looking if we found a '.' in the name.  */
1263   if (doti < name.length)
1264     {
1265       token.ptr = name.ptr;
1266       for (;;)
1267         {
1268           token.length = doti;
1269
1270           /* Handle PACKAGE.MODULE.  */
1271           typ = d_module_from_name (token);
1272           if (typ != NULL)
1273             {
1274               if (push_module_name (ps, typ, name, doti) != 0)
1275                 return;
1276             }
1277           /* Handle TYPE.FIELD1..FIELDN.  */
1278           typ = d_type_from_name (token);
1279           if (typ != NULL)
1280             {
1281               push_type_name (ps, typ, name, doti);
1282               return;
1283             }
1284
1285           if (doti >= name.length)
1286             break;
1287           doti++;   /* Skip '.'  */
1288           while (doti < name.length && name.ptr[doti] != '.')
1289             doti++;
1290         }
1291     }
1292
1293   /* Lookup foreign name in global static symbols.  */
1294   copy  = copy_name (name);
1295   msymbol = lookup_bound_minimal_symbol (copy);
1296   if (msymbol.minsym != NULL)
1297     write_exp_msymbol (ps, msymbol);
1298   else if (!have_full_symbols () && !have_partial_symbols ())
1299     error (_("No symbol table is loaded.  Use the \"file\" command"));
1300   else
1301     error (_("No symbol \"%s\" in current context."), copy);
1302 }
1303
1304 /* This is set if a NAME token appeared at the very end of the input
1305    string, with no whitespace separating the name from the EOF.  This
1306    is used only when parsing to do field name completion.  */
1307 static int saw_name_at_eof;
1308
1309 /* This is set if the previously-returned token was a structure operator.
1310    This is used only when parsing to do field name completion.  */
1311 static int last_was_structop;
1312
1313 /* Read one token, getting characters through lexptr.  */
1314
1315 static int
1316 yylex (void)
1317 {
1318   int c;
1319   int namelen;
1320   unsigned int i;
1321   const char *tokstart;
1322   int saw_structop = last_was_structop;
1323   char *copy;
1324
1325   last_was_structop = 0;
1326
1327  retry:
1328
1329   prev_lexptr = lexptr;
1330
1331   tokstart = lexptr;
1332   /* See if it is a special token of length 3.  */
1333   for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1334     if (strncmp (tokstart, tokentab3[i].oper, 3) == 0)
1335       {
1336         lexptr += 3;
1337         yylval.opcode = tokentab3[i].opcode;
1338         return tokentab3[i].token;
1339       }
1340
1341   /* See if it is a special token of length 2.  */
1342   for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1343     if (strncmp (tokstart, tokentab2[i].oper, 2) == 0)
1344       {
1345         lexptr += 2;
1346         yylval.opcode = tokentab2[i].opcode;
1347         return tokentab2[i].token;
1348       }
1349
1350   switch (c = *tokstart)
1351     {
1352     case 0:
1353       /* If we're parsing for field name completion, and the previous
1354          token allows such completion, return a COMPLETE token.
1355          Otherwise, we were already scanning the original text, and
1356          we're really done.  */
1357       if (saw_name_at_eof)
1358         {
1359           saw_name_at_eof = 0;
1360           return COMPLETE;
1361         }
1362       else if (saw_structop)
1363         return COMPLETE;
1364       else
1365         return 0;
1366
1367     case ' ':
1368     case '\t':
1369     case '\n':
1370       lexptr++;
1371       goto retry;
1372
1373     case '[':
1374     case '(':
1375       paren_depth++;
1376       lexptr++;
1377       return c;
1378
1379     case ']':
1380     case ')':
1381       if (paren_depth == 0)
1382         return 0;
1383       paren_depth--;
1384       lexptr++;
1385       return c;
1386
1387     case ',':
1388       if (comma_terminates && paren_depth == 0)
1389         return 0;
1390       lexptr++;
1391       return c;
1392
1393     case '.':
1394       /* Might be a floating point number.  */
1395       if (lexptr[1] < '0' || lexptr[1] > '9')
1396         {
1397           if (parse_completion)
1398             last_was_structop = 1;
1399           goto symbol;          /* Nope, must be a symbol.  */
1400         }
1401       /* FALL THRU into number case.  */
1402
1403     case '0':
1404     case '1':
1405     case '2':
1406     case '3':
1407     case '4':
1408     case '5':
1409     case '6':
1410     case '7':
1411     case '8':
1412     case '9':
1413       {
1414         /* It's a number.  */
1415         int got_dot = 0, got_e = 0, toktype;
1416         const char *p = tokstart;
1417         int hex = input_radix > 10;
1418
1419         if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1420           {
1421             p += 2;
1422             hex = 1;
1423           }
1424
1425         for (;; ++p)
1426           {
1427             /* Hex exponents start with 'p', because 'e' is a valid hex
1428                digit and thus does not indicate a floating point number
1429                when the radix is hex.  */
1430             if ((!hex && !got_e && tolower (p[0]) == 'e')
1431                 || (hex && !got_e && tolower (p[0] == 'p')))
1432               got_dot = got_e = 1;
1433             /* A '.' always indicates a decimal floating point number
1434                regardless of the radix.  If we have a '..' then its the
1435                end of the number and the beginning of a slice.  */
1436             else if (!got_dot && (p[0] == '.' && p[1] != '.'))
1437                 got_dot = 1;
1438             /* This is the sign of the exponent, not the end of the number.  */
1439             else if (got_e && (tolower (p[-1]) == 'e' || tolower (p[-1]) == 'p')
1440                      && (*p == '-' || *p == '+'))
1441               continue;
1442             /* We will take any letters or digits, ignoring any embedded '_'.
1443                parse_number will complain if past the radix, or if L or U are
1444                not final.  */
1445             else if ((*p < '0' || *p > '9') && (*p != '_') &&
1446                      ((*p < 'a' || *p > 'z') && (*p < 'A' || *p > 'Z')))
1447               break;
1448           }
1449
1450         toktype = parse_number (pstate, tokstart, p - tokstart,
1451                                 got_dot|got_e, &yylval);
1452         if (toktype == ERROR)
1453           {
1454             char *err_copy = (char *) alloca (p - tokstart + 1);
1455
1456             memcpy (err_copy, tokstart, p - tokstart);
1457             err_copy[p - tokstart] = 0;
1458             error (_("Invalid number \"%s\"."), err_copy);
1459           }
1460         lexptr = p;
1461         return toktype;
1462       }
1463
1464     case '@':
1465       {
1466         const char *p = &tokstart[1];
1467         size_t len = strlen ("entry");
1468
1469         while (isspace (*p))
1470           p++;
1471         if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1472             && p[len] != '_')
1473           {
1474             lexptr = &p[len];
1475             return ENTRY;
1476           }
1477       }
1478       /* FALLTHRU */
1479     case '+':
1480     case '-':
1481     case '*':
1482     case '/':
1483     case '%':
1484     case '|':
1485     case '&':
1486     case '^':
1487     case '~':
1488     case '!':
1489     case '<':
1490     case '>':
1491     case '?':
1492     case ':':
1493     case '=':
1494     case '{':
1495     case '}':
1496     symbol:
1497       lexptr++;
1498       return c;
1499
1500     case '\'':
1501     case '"':
1502     case '`':
1503       {
1504         int host_len;
1505         int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
1506                                            &host_len);
1507         if (result == CHARACTER_LITERAL)
1508           {
1509             if (host_len == 0)
1510               error (_("Empty character constant."));
1511             else if (host_len > 2 && c == '\'')
1512               {
1513                 ++tokstart;
1514                 namelen = lexptr - tokstart - 1;
1515                 goto tryname;
1516               }
1517             else if (host_len > 1)
1518               error (_("Invalid character constant."));
1519           }
1520         return result;
1521       }
1522     }
1523
1524   if (!(c == '_' || c == '$'
1525         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1526     /* We must have come across a bad character (e.g. ';').  */
1527     error (_("Invalid character '%c' in expression"), c);
1528
1529   /* It's a name.  See how long it is.  */
1530   namelen = 0;
1531   for (c = tokstart[namelen];
1532        (c == '_' || c == '$' || (c >= '0' && c <= '9')
1533         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1534     c = tokstart[++namelen];
1535
1536   /* The token "if" terminates the expression and is NOT
1537      removed from the input stream.  */
1538   if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1539     return 0;
1540
1541   /* For the same reason (breakpoint conditions), "thread N"
1542      terminates the expression.  "thread" could be an identifier, but
1543      an identifier is never followed by a number without intervening
1544      punctuation.  "task" is similar.  Handle abbreviations of these,
1545      similarly to breakpoint.c:find_condition_and_thread.  */
1546   if (namelen >= 1
1547       && (strncmp (tokstart, "thread", namelen) == 0
1548           || strncmp (tokstart, "task", namelen) == 0)
1549       && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1550     {
1551       const char *p = tokstart + namelen + 1;
1552
1553       while (*p == ' ' || *p == '\t')
1554         p++;
1555       if (*p >= '0' && *p <= '9')
1556         return 0;
1557     }
1558
1559   lexptr += namelen;
1560
1561  tryname:
1562
1563   yylval.sval.ptr = tokstart;
1564   yylval.sval.length = namelen;
1565
1566   /* Catch specific keywords.  */
1567   copy = copy_name (yylval.sval);
1568   for (i = 0; i < sizeof ident_tokens / sizeof ident_tokens[0]; i++)
1569     if (strcmp (copy, ident_tokens[i].oper) == 0)
1570       {
1571         /* It is ok to always set this, even though we don't always
1572            strictly need to.  */
1573         yylval.opcode = ident_tokens[i].opcode;
1574         return ident_tokens[i].token;
1575       }
1576
1577   if (*tokstart == '$')
1578     return DOLLAR_VARIABLE;
1579
1580   yylval.tsym.type
1581     = language_lookup_primitive_type (parse_language (pstate),
1582                                       parse_gdbarch (pstate), copy);
1583   if (yylval.tsym.type != NULL)
1584     return TYPENAME;
1585
1586   /* Input names that aren't symbols but ARE valid hex numbers,
1587      when the input radix permits them, can be names or numbers
1588      depending on the parse.  Note we support radixes > 16 here.  */
1589   if ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10)
1590       || (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10))
1591     {
1592       YYSTYPE newlval;  /* Its value is ignored.  */
1593       int hextype = parse_number (pstate, tokstart, namelen, 0, &newlval);
1594       if (hextype == INTEGER_LITERAL)
1595         return NAME_OR_INT;
1596     }
1597
1598   if (parse_completion && *lexptr == '\0')
1599     saw_name_at_eof = 1;
1600
1601   return IDENTIFIER;
1602 }
1603
1604 int
1605 d_parse (struct parser_state *par_state)
1606 {
1607   int result;
1608   struct cleanup *back_to;
1609
1610   /* Setting up the parser state.  */
1611   gdb_assert (par_state != NULL);
1612   pstate = par_state;
1613
1614   back_to = make_cleanup (null_cleanup, NULL);
1615
1616   make_cleanup_restore_integer (&yydebug);
1617   make_cleanup_clear_parser_state (&pstate);
1618   yydebug = parser_debug;
1619
1620   /* Initialize some state used by the lexer.  */
1621   last_was_structop = 0;
1622   saw_name_at_eof = 0;
1623
1624   result = yyparse ();
1625   do_cleanups (back_to);
1626   return result;
1627 }
1628
1629 void
1630 yyerror (char *msg)
1631 {
1632   if (prev_lexptr)
1633     lexptr = prev_lexptr;
1634
1635   error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);
1636 }
1637