fix memory errors with demangled name hash
[platform/upstream/binutils.git] / gdb / d-exp.y
1 /* YACC parser for D expressions, for GDB.
2
3    Copyright (C) 2014 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 <string.h>
43 #include <ctype.h>
44 #include "expression.h"
45 #include "value.h"
46 #include "parser-defs.h"
47 #include "language.h"
48 #include "c-lang.h"
49 #include "d-lang.h"
50 #include "bfd.h" /* Required by objfiles.h.  */
51 #include "symfile.h" /* Required by objfiles.h.  */
52 #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
53 #include "charset.h"
54 #include "block.h"
55
56 #define parse_type(ps) builtin_type (parse_gdbarch (ps))
57 #define parse_d_type(ps) builtin_d_type (parse_gdbarch (ps))
58
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.  */
65
66 #define yymaxdepth d_maxdepth
67 #define yyparse d_parse_internal
68 #define yylex   d_lex
69 #define yyerror d_error
70 #define yylval  d_lval
71 #define yychar  d_char
72 #define yydebug d_debug
73 #define yypact  d_pact
74 #define yyr1    d_r1
75 #define yyr2    d_r2
76 #define yydef   d_def
77 #define yychk   d_chk
78 #define yypgo   d_pgo
79 #define yyact   d_act
80 #define yyexca  d_exca
81 #define yyerrflag d_errflag
82 #define yynerrs d_nerrs
83 #define yyps    d_ps
84 #define yypv    d_pv
85 #define yys     d_s
86 #define yy_yys  d_yys
87 #define yystate d_state
88 #define yytmp   d_tmp
89 #define yyv     d_v
90 #define yy_yyv  d_yyv
91 #define yyval   d_val
92 #define yylloc  d_lloc
93 #define yyreds  d_reds  /* With YYDEBUG defined */
94 #define yytoks  d_toks  /* With YYDEBUG defined */
95 #define yyname  d_name  /* With YYDEBUG defined */
96 #define yyrule  d_rule  /* With YYDEBUG defined */
97 #define yylhs   d_yylhs
98 #define yylen   d_yylen
99 #define yydefre d_yydefred
100 #define yydgoto d_yydgoto
101 #define yysindex d_yysindex
102 #define yyrindex d_yyrindex
103 #define yygindex d_yygindex
104 #define yytable d_yytable
105 #define yycheck d_yycheck
106 #define yyss    d_yyss
107 #define yysslim d_yysslim
108 #define yyssp   d_yyssp
109 #define yystacksize d_yystacksize
110 #define yyvs    d_yyvs
111 #define yyvsp   d_yyvsp
112
113 #ifndef YYDEBUG
114 #define YYDEBUG 1       /* Default to yydebug support */
115 #endif
116
117 #define YYFPRINTF parser_fprintf
118
119 /* The state of the parser, used internally when we are parsing the
120    expression.  */
121
122 static struct parser_state *pstate = NULL;
123
124 int yyparse (void);
125
126 static int yylex (void);
127
128 void yyerror (char *);
129
130 %}
131
132 /* Although the yacc "value" of an expression is not used,
133    since the result is stored in the structure being created,
134    other node types do have values.  */
135
136 %union
137   {
138     struct {
139       LONGEST val;
140       struct type *type;
141     } typed_val_int;
142     struct {
143       DOUBLEST dval;
144       struct type *type;
145     } typed_val_float;
146     struct symbol *sym;
147     struct type *tval;
148     struct typed_stoken tsval;
149     struct stoken sval;
150     struct ttype tsym;
151     struct symtoken ssym;
152     int ival;
153     struct block *bval;
154     enum exp_opcode opcode;
155     struct stoken_vector svec;
156   }
157
158 %{
159 /* YYSTYPE gets defined by %union */
160 static int parse_number (struct parser_state *, const char *,
161                          int, int, YYSTYPE *);
162
163 static void push_expression_name (struct parser_state *, struct stoken);
164 %}
165
166 %token <sval> IDENTIFIER
167 %token <tsym> TYPENAME
168 %token <voidval> COMPLETE
169
170 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
171    but which would parse as a valid number in the current input radix.
172    E.g. "c" when input_radix==16.  Depending on the parse, it will be
173    turned into a name or into a number.  */
174
175 %token <sval> NAME_OR_INT
176
177 %token <typed_val_int> INTEGER_LITERAL
178 %token <typed_val_float> FLOAT_LITERAL
179 %token <tsval> CHARACTER_LITERAL
180 %token <tsval> STRING_LITERAL
181
182 %type <svec> StringExp
183 %type <tval> BasicType TypeExp
184 %type <sval> IdentifierExp
185 %type <ival> ArrayLiteral
186
187 %token ENTRY
188 %token ERROR
189
190 /* Keywords that have a constant value.  */
191 %token TRUE_KEYWORD FALSE_KEYWORD NULL_KEYWORD
192 /* Class 'super' accessor.  */
193 %token SUPER_KEYWORD
194 /* Properties.  */
195 %token CAST_KEYWORD SIZEOF_KEYWORD
196 %token TYPEOF_KEYWORD TYPEID_KEYWORD
197 %token INIT_KEYWORD
198 /* Comparison keywords.  */
199 /* Type storage classes.  */
200 %token IMMUTABLE_KEYWORD CONST_KEYWORD SHARED_KEYWORD
201 /* Non-scalar type keywords.  */
202 %token STRUCT_KEYWORD UNION_KEYWORD
203 %token CLASS_KEYWORD INTERFACE_KEYWORD
204 %token ENUM_KEYWORD TEMPLATE_KEYWORD
205 %token DELEGATE_KEYWORD FUNCTION_KEYWORD
206
207 %token <sval> DOLLAR_VARIABLE
208
209 %token <opcode> ASSIGN_MODIFY
210
211 %left ','
212 %right '=' ASSIGN_MODIFY
213 %right '?'
214 %left OROR
215 %left ANDAND
216 %left '|'
217 %left '^'
218 %left '&'
219 %left EQUAL NOTEQUAL '<' '>' LEQ GEQ
220 %right LSH RSH
221 %left '+' '-'
222 %left '*' '/' '%'
223 %right HATHAT
224 %left IDENTITY NOTIDENTITY
225 %right INCREMENT DECREMENT
226 %right '.' '[' '('
227 %token DOTDOT
228
229 \f
230 %%
231
232 start   :
233         Expression
234 |       TypeExp
235 ;
236
237 /* Expressions, including the comma operator.  */
238
239 Expression:
240         CommaExpression
241 ;
242
243 CommaExpression:
244         AssignExpression
245 |       AssignExpression ',' CommaExpression
246                 { write_exp_elt_opcode (pstate, BINOP_COMMA); }
247 ;
248
249 AssignExpression:
250         ConditionalExpression
251 |       ConditionalExpression '=' AssignExpression
252                 { write_exp_elt_opcode (pstate, BINOP_ASSIGN); }
253 |       ConditionalExpression ASSIGN_MODIFY AssignExpression
254                 { write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY);
255                   write_exp_elt_opcode (pstate, $2);
256                   write_exp_elt_opcode (pstate, BINOP_ASSIGN_MODIFY); }
257 ;
258
259 ConditionalExpression:
260         OrOrExpression
261 |       OrOrExpression '?' Expression ':' ConditionalExpression
262                 { write_exp_elt_opcode (pstate, TERNOP_COND); }
263 ;
264
265 OrOrExpression:
266         AndAndExpression
267 |       OrOrExpression OROR AndAndExpression
268                 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_OR); }
269 ;
270
271 AndAndExpression:
272         OrExpression
273 |       AndAndExpression ANDAND OrExpression
274                 { write_exp_elt_opcode (pstate, BINOP_LOGICAL_AND); }
275 ;
276
277 OrExpression:
278         XorExpression
279 |       OrExpression '|' XorExpression
280                 { write_exp_elt_opcode (pstate, BINOP_BITWISE_IOR); }
281 ;
282
283 XorExpression:
284         AndExpression
285 |       XorExpression '^' AndExpression
286                 { write_exp_elt_opcode (pstate, BINOP_BITWISE_XOR); }
287 ;
288
289 AndExpression:
290         CmpExpression
291 |       AndExpression '&' CmpExpression
292                 { write_exp_elt_opcode (pstate, BINOP_BITWISE_AND); }
293 ;
294
295 CmpExpression:
296         ShiftExpression
297 |       EqualExpression
298 |       IdentityExpression
299 |       RelExpression
300 ;
301
302 EqualExpression:
303         ShiftExpression EQUAL ShiftExpression
304                 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
305 |       ShiftExpression NOTEQUAL ShiftExpression
306                 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
307 ;
308
309 IdentityExpression:
310         ShiftExpression IDENTITY ShiftExpression
311                 { write_exp_elt_opcode (pstate, BINOP_EQUAL); }
312 |       ShiftExpression NOTIDENTITY ShiftExpression
313                 { write_exp_elt_opcode (pstate, BINOP_NOTEQUAL); }
314 ;
315
316 RelExpression:
317         ShiftExpression '<' ShiftExpression
318                 { write_exp_elt_opcode (pstate, BINOP_LESS); }
319 |       ShiftExpression LEQ ShiftExpression
320                 { write_exp_elt_opcode (pstate, BINOP_LEQ); }
321 |       ShiftExpression '>' ShiftExpression
322                 { write_exp_elt_opcode (pstate, BINOP_GTR); }
323 |       ShiftExpression GEQ ShiftExpression
324                 { write_exp_elt_opcode (pstate, BINOP_GEQ); }
325 ;
326
327 ShiftExpression:
328         AddExpression
329 |       ShiftExpression LSH AddExpression
330                 { write_exp_elt_opcode (pstate, BINOP_LSH); }
331 |       ShiftExpression RSH AddExpression
332                 { write_exp_elt_opcode (pstate, BINOP_RSH); }
333 ;
334
335 AddExpression:
336         MulExpression
337 |       AddExpression '+' MulExpression
338                 { write_exp_elt_opcode (pstate, BINOP_ADD); }
339 |       AddExpression '-' MulExpression
340                 { write_exp_elt_opcode (pstate, BINOP_SUB); }
341 |       AddExpression '~' MulExpression
342                 { write_exp_elt_opcode (pstate, BINOP_CONCAT); }
343 ;
344
345 MulExpression:
346         UnaryExpression
347 |       MulExpression '*' UnaryExpression
348                 { write_exp_elt_opcode (pstate, BINOP_MUL); }
349 |       MulExpression '/' UnaryExpression
350                 { write_exp_elt_opcode (pstate, BINOP_DIV); }
351 |       MulExpression '%' UnaryExpression
352                 { write_exp_elt_opcode (pstate, BINOP_REM); }
353
354 UnaryExpression:
355         '&' UnaryExpression
356                 { write_exp_elt_opcode (pstate, UNOP_ADDR); }
357 |       INCREMENT UnaryExpression
358                 { write_exp_elt_opcode (pstate, UNOP_PREINCREMENT); }
359 |       DECREMENT UnaryExpression
360                 { write_exp_elt_opcode (pstate, UNOP_PREDECREMENT); }
361 |       '*' UnaryExpression
362                 { write_exp_elt_opcode (pstate, UNOP_IND); }
363 |       '-' UnaryExpression
364                 { write_exp_elt_opcode (pstate, UNOP_NEG); }
365 |       '+' UnaryExpression
366                 { write_exp_elt_opcode (pstate, UNOP_PLUS); }
367 |       '!' UnaryExpression
368                 { write_exp_elt_opcode (pstate, UNOP_LOGICAL_NOT); }
369 |       '~' UnaryExpression
370                 { write_exp_elt_opcode (pstate, UNOP_COMPLEMENT); }
371 |       CastExpression
372 |       PowExpression
373 ;
374
375 CastExpression:
376         CAST_KEYWORD '(' TypeExp ')' UnaryExpression
377                 { write_exp_elt_opcode (pstate, UNOP_CAST);
378                   write_exp_elt_type (pstate, $3);
379                   write_exp_elt_opcode (pstate, UNOP_CAST); }
380         /* C style cast is illegal D, but is still recognised in
381            the grammar, so we keep this around for convenience.  */
382 |       '(' TypeExp ')' UnaryExpression
383                 { write_exp_elt_opcode (pstate, UNOP_CAST);
384                   write_exp_elt_type (pstate, $2);
385                   write_exp_elt_opcode (pstate, UNOP_CAST); }
386 ;
387
388 PowExpression:
389         PostfixExpression
390 |       PostfixExpression HATHAT UnaryExpression
391                 { write_exp_elt_opcode (pstate, BINOP_EXP); }
392 ;
393
394 PostfixExpression:
395         PrimaryExpression
396 |       PostfixExpression INCREMENT
397                 { write_exp_elt_opcode (pstate, UNOP_POSTINCREMENT); }
398 |       PostfixExpression DECREMENT
399                 { write_exp_elt_opcode (pstate, UNOP_POSTDECREMENT); }
400 |       CallExpression
401 |       IndexExpression
402 |       SliceExpression
403 ;
404
405 ArgumentList:
406         AssignExpression
407                 { arglist_len = 1; }
408 |       ArgumentList ',' AssignExpression
409                 { arglist_len++; }
410 ;
411
412 ArgumentList_opt:
413         /* EMPTY */
414                 { arglist_len = 0; }
415 |       ArgumentList
416 ;
417
418 CallExpression:
419         PostfixExpression '('
420                 { start_arglist (); }
421         ArgumentList_opt ')'
422                 { write_exp_elt_opcode (pstate, OP_FUNCALL);
423                   write_exp_elt_longcst (pstate, (LONGEST) end_arglist ());
424                   write_exp_elt_opcode (pstate, OP_FUNCALL); }
425 ;
426
427 IndexExpression:
428         PostfixExpression '[' ArgumentList ']'
429                 { if (arglist_len > 0)
430                     {
431                       write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
432                       write_exp_elt_longcst (pstate, (LONGEST) arglist_len);
433                       write_exp_elt_opcode (pstate, MULTI_SUBSCRIPT);
434                     }
435                   else
436                     write_exp_elt_opcode (pstate, BINOP_SUBSCRIPT);
437                 }
438 ;
439
440 SliceExpression:
441         PostfixExpression '[' ']'
442                 { /* Do nothing.  */ }
443 |       PostfixExpression '[' AssignExpression DOTDOT AssignExpression ']'
444                 { write_exp_elt_opcode (pstate, TERNOP_SLICE); }
445 ;
446
447 PrimaryExpression:
448         '(' Expression ')'
449                 { /* Do nothing.  */ }
450 |       IdentifierExp
451                 { push_expression_name (pstate, $1); }
452 |       IdentifierExp '.' COMPLETE
453                 { struct stoken s;
454                   s.ptr = "";
455                   s.length = 0;
456                   push_expression_name (pstate, $1);
457                   mark_struct_expression (pstate);
458                   write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
459                   write_exp_string (pstate, s);
460                   write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
461 |       IdentifierExp '.' IDENTIFIER COMPLETE
462                 { push_expression_name (pstate, $1);
463                   mark_struct_expression (pstate);
464                   write_exp_elt_opcode (pstate, STRUCTOP_STRUCT);
465                   write_exp_string (pstate, $3);
466                   write_exp_elt_opcode (pstate, STRUCTOP_STRUCT); }
467 |       DOLLAR_VARIABLE
468                 { write_dollar_variable (pstate, $1); }
469 |       NAME_OR_INT
470                 { YYSTYPE val;
471                   parse_number (pstate, $1.ptr, $1.length, 0, &val);
472                   write_exp_elt_opcode (pstate, OP_LONG);
473                   write_exp_elt_type (pstate, val.typed_val_int.type);
474                   write_exp_elt_longcst (pstate,
475                                          (LONGEST) val.typed_val_int.val);
476                   write_exp_elt_opcode (pstate, OP_LONG); }
477 |       NULL_KEYWORD
478                 { struct type *type = parse_d_type (pstate)->builtin_void;
479                   type = lookup_pointer_type (type);
480                   write_exp_elt_opcode (pstate, OP_LONG);
481                   write_exp_elt_type (pstate, type);
482                   write_exp_elt_longcst (pstate, (LONGEST) 0);
483                   write_exp_elt_opcode (pstate, OP_LONG); }
484 |       TRUE_KEYWORD
485                 { write_exp_elt_opcode (pstate, OP_BOOL);
486                   write_exp_elt_longcst (pstate, (LONGEST) 1);
487                   write_exp_elt_opcode (pstate, OP_BOOL); }
488 |       FALSE_KEYWORD
489                 { write_exp_elt_opcode (pstate, OP_BOOL);
490                   write_exp_elt_longcst (pstate, (LONGEST) 0);
491                   write_exp_elt_opcode (pstate, OP_BOOL); }
492 |       INTEGER_LITERAL
493                 { write_exp_elt_opcode (pstate, OP_LONG);
494                   write_exp_elt_type (pstate, $1.type);
495                   write_exp_elt_longcst (pstate, (LONGEST)($1.val));
496                   write_exp_elt_opcode (pstate, OP_LONG); }
497 |       FLOAT_LITERAL
498                 { write_exp_elt_opcode (pstate, OP_DOUBLE);
499                   write_exp_elt_type (pstate, $1.type);
500                   write_exp_elt_dblcst (pstate, $1.dval);
501                   write_exp_elt_opcode (pstate, OP_DOUBLE); }
502 |       CHARACTER_LITERAL
503                 { struct stoken_vector vec;
504                   vec.len = 1;
505                   vec.tokens = &$1;
506                   write_exp_string_vector (pstate, $1.type, &vec); }
507 |       StringExp
508                 { int i;
509                   write_exp_string_vector (pstate, 0, &$1);
510                   for (i = 0; i < $1.len; ++i)
511                     free ($1.tokens[i].ptr);
512                   free ($1.tokens); }
513 |       ArrayLiteral
514                 { write_exp_elt_opcode (pstate, OP_ARRAY);
515                   write_exp_elt_longcst (pstate, (LONGEST) 0);
516                   write_exp_elt_longcst (pstate, (LONGEST) $1 - 1);
517                   write_exp_elt_opcode (pstate, OP_ARRAY); }
518 ;
519
520 ArrayLiteral:
521         '[' ArgumentList_opt ']'
522                 { $$ = arglist_len; }
523 ;
524
525 IdentifierExp:
526         IDENTIFIER
527 |       IdentifierExp '.' IDENTIFIER
528                 { $$.length = $1.length + $3.length + 1;
529                   if ($1.ptr + $1.length + 1 == $3.ptr
530                       && $1.ptr[$1.length] == '.')
531                     $$.ptr = $1.ptr;  /* Optimization.  */
532                   else
533                     {
534                       char *buf = malloc ($$.length + 1);
535                       make_cleanup (free, buf);
536                       sprintf (buf, "%.*s.%.*s",
537                                $1.length, $1.ptr, $3.length, $3.ptr);
538                       $$.ptr = buf;
539                     }
540                 }
541 ;
542
543 StringExp:
544         STRING_LITERAL
545                 { /* We copy the string here, and not in the
546                      lexer, to guarantee that we do not leak a
547                      string.  Note that we follow the
548                      NUL-termination convention of the
549                      lexer.  */
550                   struct typed_stoken *vec = XNEW (struct typed_stoken);
551                   $$.len = 1;
552                   $$.tokens = vec;
553
554                   vec->type = $1.type;
555                   vec->length = $1.length;
556                   vec->ptr = malloc ($1.length + 1);
557                   memcpy (vec->ptr, $1.ptr, $1.length + 1);
558                 }
559 |       StringExp STRING_LITERAL
560                 { /* Note that we NUL-terminate here, but just
561                      for convenience.  */
562                   char *p;
563                   ++$$.len;
564                   $$.tokens = realloc ($$.tokens,
565                                        $$.len * sizeof (struct typed_stoken));
566
567                   p = malloc ($2.length + 1);
568                   memcpy (p, $2.ptr, $2.length + 1);
569
570                   $$.tokens[$$.len - 1].type = $2.type;
571                   $$.tokens[$$.len - 1].length = $2.length;
572                   $$.tokens[$$.len - 1].ptr = p;
573                 }
574 ;
575
576 TypeExp:
577         BasicType
578                 { write_exp_elt_opcode (pstate, OP_TYPE);
579                   write_exp_elt_type (pstate, $1);
580                   write_exp_elt_opcode (pstate, OP_TYPE); }
581 |       BasicType BasicType2
582                 { $$ = follow_types ($1);
583                   write_exp_elt_opcode (pstate, OP_TYPE);
584                   write_exp_elt_type (pstate, $$);
585                   write_exp_elt_opcode (pstate, OP_TYPE);
586                 }
587 ;
588
589 BasicType2:
590         '*'
591                 { push_type (tp_pointer); }
592 |       '*' BasicType2
593                 { push_type (tp_pointer); }
594 |       '[' INTEGER_LITERAL ']'
595                 { push_type_int ($2.val);
596                   push_type (tp_array); }
597 |       '[' INTEGER_LITERAL ']' BasicType2
598                 { push_type_int ($2.val);
599                   push_type (tp_array); }
600 ;
601
602 BasicType:
603         TYPENAME
604                 { $$ = $1.type; }
605 |       CLASS_KEYWORD IdentifierExp
606                 { $$ = lookup_struct (copy_name ($2),
607                                       expression_context_block); }
608 |       CLASS_KEYWORD COMPLETE
609                 { mark_completion_tag (TYPE_CODE_CLASS, "", 0);
610                   $$ = NULL; }
611 |       CLASS_KEYWORD IdentifierExp COMPLETE
612                 { mark_completion_tag (TYPE_CODE_CLASS, $2.ptr, $2.length);
613                   $$ = NULL; }
614 |       STRUCT_KEYWORD IdentifierExp
615                 { $$ = lookup_struct (copy_name ($2),
616                                       expression_context_block); }
617 |       STRUCT_KEYWORD COMPLETE
618                 { mark_completion_tag (TYPE_CODE_STRUCT, "", 0);
619                   $$ = NULL; }
620 |       STRUCT_KEYWORD IdentifierExp COMPLETE
621                 { mark_completion_tag (TYPE_CODE_STRUCT, $2.ptr, $2.length);
622                   $$ = NULL; }
623 |       UNION_KEYWORD IdentifierExp
624                 { $$ = lookup_union (copy_name ($2),
625                                      expression_context_block); }
626 |       UNION_KEYWORD COMPLETE
627                 { mark_completion_tag (TYPE_CODE_UNION, "", 0);
628                   $$ = NULL; }
629 |       UNION_KEYWORD IdentifierExp COMPLETE
630                 { mark_completion_tag (TYPE_CODE_UNION, $2.ptr, $2.length);
631                   $$ = NULL; }
632 |       ENUM_KEYWORD IdentifierExp
633                 { $$ = lookup_enum (copy_name ($2),
634                                     expression_context_block); }
635 |       ENUM_KEYWORD COMPLETE
636                 { mark_completion_tag (TYPE_CODE_ENUM, "", 0);
637                   $$ = NULL; }
638 |       ENUM_KEYWORD IdentifierExp COMPLETE
639                 { mark_completion_tag (TYPE_CODE_ENUM, $2.ptr, $2.length);
640                   $$ = NULL; }
641 ;
642
643 %%
644
645 /* Take care of parsing a number (anything that starts with a digit).
646    Set yylval and return the token type; update lexptr.
647    LEN is the number of characters in it.  */
648
649 /*** Needs some error checking for the float case ***/
650
651 static int
652 parse_number (struct parser_state *ps, const char *p,
653               int len, int parsed_float, YYSTYPE *putithere)
654 {
655   ULONGEST n = 0;
656   ULONGEST prevn = 0;
657   ULONGEST un;
658
659   int i = 0;
660   int c;
661   int base = input_radix;
662   int unsigned_p = 0;
663   int long_p = 0;
664
665   /* We have found a "L" or "U" suffix.  */
666   int found_suffix = 0;
667
668   ULONGEST high_bit;
669   struct type *signed_type;
670   struct type *unsigned_type;
671
672   if (parsed_float)
673     {
674       const struct builtin_d_type *builtin_d_types;
675       const char *suffix;
676       int suffix_len;
677       char *s, *sp;
678
679       /* Strip out all embedded '_' before passing to parse_float.  */
680       s = (char *) alloca (len + 1);
681       sp = s;
682       while (len-- > 0)
683         {
684           if (*p != '_')
685             *sp++ = *p;
686           p++;
687         }
688       *sp = '\0';
689       len = strlen (s);
690
691       if (! parse_float (s, len, &putithere->typed_val_float.dval, &suffix))
692         return ERROR;
693
694       suffix_len = s + len - suffix;
695
696       if (suffix_len == 0)
697         {
698           putithere->typed_val_float.type
699             = parse_d_type (ps)->builtin_double;
700         }
701       else if (suffix_len == 1)
702         {
703           /* Check suffix for `f', `l', or `i' (float, real, or idouble).  */
704           if (tolower (*suffix) == 'f')
705             {
706               putithere->typed_val_float.type
707                 = parse_d_type (ps)->builtin_float;
708             }
709           else if (tolower (*suffix) == 'l')
710             {
711               putithere->typed_val_float.type
712                 = parse_d_type (ps)->builtin_real;
713             }
714           else if (tolower (*suffix) == 'i')
715             {
716               putithere->typed_val_float.type
717                 = parse_d_type (ps)->builtin_idouble;
718             }
719           else
720             return ERROR;
721         }
722       else if (suffix_len == 2)
723         {
724           /* Check suffix for `fi' or `li' (ifloat or ireal).  */
725           if (tolower (suffix[0]) == 'f' && tolower (suffix[1] == 'i'))
726             {
727               putithere->typed_val_float.type
728                 = parse_d_type (ps)->builtin_ifloat;
729             }
730           else if (tolower (suffix[0]) == 'l' && tolower (suffix[1] == 'i'))
731             {
732               putithere->typed_val_float.type
733                 = parse_d_type (ps)->builtin_ireal;
734             }
735           else
736             return ERROR;
737         }
738       else
739         return ERROR;
740
741       return FLOAT_LITERAL;
742     }
743
744   /* Handle base-switching prefixes 0x, 0b, 0 */
745   if (p[0] == '0')
746     switch (p[1])
747       {
748       case 'x':
749       case 'X':
750         if (len >= 3)
751           {
752             p += 2;
753             base = 16;
754             len -= 2;
755           }
756         break;
757
758       case 'b':
759       case 'B':
760         if (len >= 3)
761           {
762             p += 2;
763             base = 2;
764             len -= 2;
765           }
766         break;
767
768       default:
769         base = 8;
770         break;
771       }
772
773   while (len-- > 0)
774     {
775       c = *p++;
776       if (c == '_')
777         continue;       /* Ignore embedded '_'.  */
778       if (c >= 'A' && c <= 'Z')
779         c += 'a' - 'A';
780       if (c != 'l' && c != 'u')
781         n *= base;
782       if (c >= '0' && c <= '9')
783         {
784           if (found_suffix)
785             return ERROR;
786           n += i = c - '0';
787         }
788       else
789         {
790           if (base > 10 && c >= 'a' && c <= 'f')
791             {
792               if (found_suffix)
793                 return ERROR;
794               n += i = c - 'a' + 10;
795             }
796           else if (c == 'l' && long_p == 0)
797             {
798               long_p = 1;
799               found_suffix = 1;
800             }
801           else if (c == 'u' && unsigned_p == 0)
802             {
803               unsigned_p = 1;
804               found_suffix = 1;
805             }
806           else
807             return ERROR;       /* Char not a digit */
808         }
809       if (i >= base)
810         return ERROR;           /* Invalid digit in this base.  */
811       /* Portably test for integer overflow.  */
812       if (c != 'l' && c != 'u')
813         {
814           ULONGEST n2 = prevn * base;
815           if ((n2 / base != prevn) || (n2 + i < prevn))
816             error (_("Numeric constant too large."));
817         }
818       prevn = n;
819     }
820
821   /* An integer constant is an int or a long.  An L suffix forces it to
822      be long, and a U suffix forces it to be unsigned.  To figure out
823      whether it fits, we shift it right and see whether anything remains.
824      Note that we can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or
825      more in one operation, because many compilers will warn about such a
826      shift (which always produces a zero result).  To deal with the case
827      where it is we just always shift the value more than once, with fewer
828      bits each time.  */
829   un = (ULONGEST) n >> 2;
830   if (long_p == 0 && (un >> 30) == 0)
831     {
832       high_bit = ((ULONGEST) 1) << 31;
833       signed_type = parse_d_type (ps)->builtin_int;
834       /* For decimal notation, keep the sign of the worked out type.  */
835       if (base == 10 && !unsigned_p)
836         unsigned_type = parse_d_type (ps)->builtin_long;
837       else
838         unsigned_type = parse_d_type (ps)->builtin_uint;
839     }
840   else
841     {
842       int shift;
843       if (sizeof (ULONGEST) * HOST_CHAR_BIT < 64)
844         /* A long long does not fit in a LONGEST.  */
845         shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
846       else
847         shift = 63;
848       high_bit = (ULONGEST) 1 << shift;
849       signed_type = parse_d_type (ps)->builtin_long;
850       unsigned_type = parse_d_type (ps)->builtin_ulong;
851     }
852
853   putithere->typed_val_int.val = n;
854
855   /* If the high bit of the worked out type is set then this number
856      has to be unsigned_type.  */
857   if (unsigned_p || (n & high_bit))
858     putithere->typed_val_int.type = unsigned_type;
859   else
860     putithere->typed_val_int.type = signed_type;
861
862   return INTEGER_LITERAL;
863 }
864
865 /* Temporary obstack used for holding strings.  */
866 static struct obstack tempbuf;
867 static int tempbuf_init;
868
869 /* Parse a string or character literal from TOKPTR.  The string or
870    character may be wide or unicode.  *OUTPTR is set to just after the
871    end of the literal in the input string.  The resulting token is
872    stored in VALUE.  This returns a token value, either STRING or
873    CHAR, depending on what was parsed.  *HOST_CHARS is set to the
874    number of host characters in the literal.  */
875
876 static int
877 parse_string_or_char (const char *tokptr, const char **outptr,
878                       struct typed_stoken *value, int *host_chars)
879 {
880   int quote;
881
882   /* Build the gdb internal form of the input string in tempbuf.  Note
883      that the buffer is null byte terminated *only* for the
884      convenience of debugging gdb itself and printing the buffer
885      contents when the buffer contains no embedded nulls.  Gdb does
886      not depend upon the buffer being null byte terminated, it uses
887      the length string instead.  This allows gdb to handle C strings
888      (as well as strings in other languages) with embedded null
889      bytes */
890
891   if (!tempbuf_init)
892     tempbuf_init = 1;
893   else
894     obstack_free (&tempbuf, NULL);
895   obstack_init (&tempbuf);
896
897   /* Skip the quote.  */
898   quote = *tokptr;
899   ++tokptr;
900
901   *host_chars = 0;
902
903   while (*tokptr)
904     {
905       char c = *tokptr;
906       if (c == '\\')
907         {
908            ++tokptr;
909            *host_chars += c_parse_escape (&tokptr, &tempbuf);
910         }
911       else if (c == quote)
912         break;
913       else
914         {
915           obstack_1grow (&tempbuf, c);
916           ++tokptr;
917           /* FIXME: this does the wrong thing with multi-byte host
918              characters.  We could use mbrlen here, but that would
919              make "set host-charset" a bit less useful.  */
920           ++*host_chars;
921         }
922     }
923
924   if (*tokptr != quote)
925     {
926       if (quote == '"' || quote == '`')
927         error (_("Unterminated string in expression."));
928       else
929         error (_("Unmatched single quote."));
930     }
931   ++tokptr;
932
933   /* FIXME: should instead use own language string_type enum
934      and handle D-specific string suffixes here. */
935   if (quote == '\'')
936     value->type = C_CHAR;
937   else
938     value->type = C_STRING;
939
940   value->ptr = obstack_base (&tempbuf);
941   value->length = obstack_object_size (&tempbuf);
942
943   *outptr = tokptr;
944
945   return quote == '\'' ? CHARACTER_LITERAL : STRING_LITERAL;
946 }
947
948 struct token
949 {
950   char *operator;
951   int token;
952   enum exp_opcode opcode;
953 };
954
955 static const struct token tokentab3[] =
956   {
957     {"^^=", ASSIGN_MODIFY, BINOP_EXP},
958     {"<<=", ASSIGN_MODIFY, BINOP_LSH},
959     {">>=", ASSIGN_MODIFY, BINOP_RSH},
960   };
961
962 static const struct token tokentab2[] =
963   {
964     {"+=", ASSIGN_MODIFY, BINOP_ADD},
965     {"-=", ASSIGN_MODIFY, BINOP_SUB},
966     {"*=", ASSIGN_MODIFY, BINOP_MUL},
967     {"/=", ASSIGN_MODIFY, BINOP_DIV},
968     {"%=", ASSIGN_MODIFY, BINOP_REM},
969     {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
970     {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
971     {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
972     {"++", INCREMENT, BINOP_END},
973     {"--", DECREMENT, BINOP_END},
974     {"&&", ANDAND, BINOP_END},
975     {"||", OROR, BINOP_END},
976     {"^^", HATHAT, BINOP_END},
977     {"<<", LSH, BINOP_END},
978     {">>", RSH, BINOP_END},
979     {"==", EQUAL, BINOP_END},
980     {"!=", NOTEQUAL, BINOP_END},
981     {"<=", LEQ, BINOP_END},
982     {">=", GEQ, BINOP_END},
983     {"..", DOTDOT, BINOP_END},
984   };
985
986 /* Identifier-like tokens.  */
987 static const struct token ident_tokens[] =
988   {
989     {"is", IDENTITY, BINOP_END},
990     {"!is", NOTIDENTITY, BINOP_END},
991
992     {"cast", CAST_KEYWORD, OP_NULL},
993     {"const", CONST_KEYWORD, OP_NULL},
994     {"immutable", IMMUTABLE_KEYWORD, OP_NULL},
995     {"shared", SHARED_KEYWORD, OP_NULL},
996     {"super", SUPER_KEYWORD, OP_NULL},
997
998     {"null", NULL_KEYWORD, OP_NULL},
999     {"true", TRUE_KEYWORD, OP_NULL},
1000     {"false", FALSE_KEYWORD, OP_NULL},
1001
1002     {"init", INIT_KEYWORD, OP_NULL},
1003     {"sizeof", SIZEOF_KEYWORD, OP_NULL},
1004     {"typeof", TYPEOF_KEYWORD, OP_NULL},
1005     {"typeid", TYPEID_KEYWORD, OP_NULL},
1006
1007     {"delegate", DELEGATE_KEYWORD, OP_NULL},
1008     {"function", FUNCTION_KEYWORD, OP_NULL},
1009     {"struct", STRUCT_KEYWORD, OP_NULL},
1010     {"union", UNION_KEYWORD, OP_NULL},
1011     {"class", CLASS_KEYWORD, OP_NULL},
1012     {"interface", INTERFACE_KEYWORD, OP_NULL},
1013     {"enum", ENUM_KEYWORD, OP_NULL},
1014     {"template", TEMPLATE_KEYWORD, OP_NULL},
1015   };
1016
1017 /* If NAME is a type name in this scope, return it.  */
1018
1019 static struct type *
1020 d_type_from_name (struct stoken name)
1021 {
1022   struct symbol *sym;
1023   char *copy = copy_name (name);
1024
1025   sym = lookup_symbol (copy, expression_context_block,
1026                        STRUCT_DOMAIN, NULL);
1027   if (sym != NULL)
1028     return SYMBOL_TYPE (sym);
1029
1030   return NULL;
1031 }
1032
1033 /* If NAME is a module name in this scope, return it.  */
1034
1035 static struct type *
1036 d_module_from_name (struct stoken name)
1037 {
1038   struct symbol *sym;
1039   char *copy = copy_name (name);
1040
1041   sym = lookup_symbol (copy, expression_context_block,
1042                        MODULE_DOMAIN, NULL);
1043   if (sym != NULL)
1044     return SYMBOL_TYPE (sym);
1045
1046   return NULL;
1047 }
1048
1049 /* If NAME is a valid variable name in this scope, push it and return 1.
1050    Otherwise, return 0.  */
1051
1052 static int
1053 push_variable (struct parser_state *ps, struct stoken name)
1054 {
1055   char *copy = copy_name (name);
1056   struct field_of_this_result is_a_field_of_this;
1057   struct symbol *sym;
1058   sym = lookup_symbol (copy, expression_context_block, VAR_DOMAIN,
1059                        &is_a_field_of_this);
1060   if (sym && SYMBOL_CLASS (sym) != LOC_TYPEDEF)
1061     {
1062       if (symbol_read_needs_frame (sym))
1063         {
1064           if (innermost_block == 0 ||
1065               contained_in (block_found, innermost_block))
1066             innermost_block = block_found;
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);
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 (block_found, innermost_block))
1083         innermost_block = block_found;
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_static (copy, expression_context_block,
1184                                   VAR_DOMAIN);
1185       if (sym != NULL)
1186         sym = lookup_symbol_global (copy, expression_context_block,
1187                                     VAR_DOMAIN);
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].operator, 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].operator, 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].operator) == 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_by_name (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