Fix PR rust/20110
[external/binutils.git] / gdb / rust-exp.y
1 /* Bison parser for Rust expressions, for GDB.
2    Copyright (C) 2016 Free Software Foundation, Inc.
3
4    This file is part of GDB.
5
6    This program is free software; you can redistribute it and/or modify
7    it under the terms of the GNU General Public License as published by
8    the Free Software Foundation; either version 3 of the License, or
9    (at your option) any later version.
10
11    This program is distributed in the hope that it will be useful,
12    but WITHOUT ANY WARRANTY; without even the implied warranty of
13    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14    GNU General Public License for more details.
15
16    You should have received a copy of the GNU General Public License
17    along with this program.  If not, see <http://www.gnu.org/licenses/>.  */
18
19 /* Removing the last conflict seems difficult.  */
20 %expect 1
21
22 %{
23
24 #include "defs.h"
25
26 #include "block.h"
27 #include "charset.h"
28 #include "cp-support.h"
29 #include "gdb_obstack.h"
30 #include "gdb_regex.h"
31 #include "rust-lang.h"
32 #include "parser-defs.h"
33 #include "selftest.h"
34 #include "value.h"
35 #include "vec.h"
36
37 #define GDB_YY_REMAP_PREFIX rust
38 #include "yy-remap.h"
39
40 #define RUSTSTYPE YYSTYPE
41
42 extern initialize_file_ftype _initialize_rust_exp;
43
44 struct rust_op;
45 typedef const struct rust_op *rust_op_ptr;
46 DEF_VEC_P (rust_op_ptr);
47
48 /* A typed integer constant.  */
49
50 struct typed_val_int
51 {
52   LONGEST val;
53   struct type *type;
54 };
55
56 /* A typed floating point constant.  */
57
58 struct typed_val_float
59 {
60   DOUBLEST dval;
61   struct type *type;
62 };
63
64 /* An identifier and an expression.  This is used to represent one
65    element of a struct initializer.  */
66
67 struct set_field
68 {
69   struct stoken name;
70   const struct rust_op *init;
71 };
72
73 typedef struct set_field set_field;
74
75 DEF_VEC_O (set_field);
76
77
78 static int rustyylex (void);
79 static void rust_push_back (char c);
80 static const char *rust_copy_name (const char *, int);
81 static struct stoken rust_concat3 (const char *, const char *, const char *);
82 static struct stoken make_stoken (const char *);
83 static struct block_symbol rust_lookup_symbol (const char *name,
84                                                const struct block *block,
85                                                const domain_enum domain);
86 static struct type *rust_lookup_type (const char *name,
87                                       const struct block *block);
88 static struct type *rust_type (const char *name);
89
90 static const struct rust_op *crate_name (const struct rust_op *name);
91 static const struct rust_op *super_name (const struct rust_op *name,
92                                          unsigned int n_supers);
93
94 static const struct rust_op *ast_operation (enum exp_opcode opcode,
95                                             const struct rust_op *left,
96                                             const struct rust_op *right);
97 static const struct rust_op *ast_compound_assignment
98   (enum exp_opcode opcode, const struct rust_op *left,
99    const struct rust_op *rust_op);
100 static const struct rust_op *ast_literal (struct typed_val_int val);
101 static const struct rust_op *ast_dliteral (struct typed_val_float val);
102 static const struct rust_op *ast_structop (const struct rust_op *left,
103                                            const char *name,
104                                            int completing);
105 static const struct rust_op *ast_structop_anonymous
106   (const struct rust_op *left, struct typed_val_int number);
107 static const struct rust_op *ast_unary (enum exp_opcode opcode,
108                                         const struct rust_op *expr);
109 static const struct rust_op *ast_cast (const struct rust_op *expr,
110                                        const struct rust_op *type);
111 static const struct rust_op *ast_call_ish (enum exp_opcode opcode,
112                                            const struct rust_op *expr,
113                                            VEC (rust_op_ptr) **params);
114 static const struct rust_op *ast_path (struct stoken name,
115                                        VEC (rust_op_ptr) **params);
116 static const struct rust_op *ast_string (struct stoken str);
117 static const struct rust_op *ast_struct (const struct rust_op *name,
118                                          VEC (set_field) **fields);
119 static const struct rust_op *ast_range (const struct rust_op *lhs,
120                                         const struct rust_op *rhs);
121 static const struct rust_op *ast_array_type (const struct rust_op *lhs,
122                                              struct typed_val_int val);
123 static const struct rust_op *ast_slice_type (const struct rust_op *type);
124 static const struct rust_op *ast_reference_type (const struct rust_op *type);
125 static const struct rust_op *ast_pointer_type (const struct rust_op *type,
126                                                int is_mut);
127 static const struct rust_op *ast_function_type (const struct rust_op *result,
128                                                 VEC (rust_op_ptr) **params);
129 static const struct rust_op *ast_tuple_type (VEC (rust_op_ptr) **params);
130
131 /* The state of the parser, used internally when we are parsing the
132    expression.  */
133
134 static struct parser_state *pstate = NULL;
135
136 /* A regular expression for matching Rust numbers.  This is split up
137    since it is very long and this gives us a way to comment the
138    sections.  */
139
140 static const char *number_regex_text =
141   /* subexpression 1: allows use of alternation, otherwise uninteresting */
142   "^("
143   /* First comes floating point.  */
144   /* Recognize number after the decimal point, with optional
145      exponent and optional type suffix.
146      subexpression 2: allows "?", otherwise uninteresting
147      subexpression 3: if present, type suffix
148   */
149   "[0-9][0-9_]*\\.[0-9][0-9_]*([eE][-+]?[0-9][0-9_]*)?(f32|f64)?"
150 #define FLOAT_TYPE1 3
151   "|"
152   /* Recognize exponent without decimal point, with optional type
153      suffix.
154      subexpression 4: if present, type suffix
155   */
156 #define FLOAT_TYPE2 4
157   "[0-9][0-9_]*[eE][-+]?[0-9][0-9_]*(f32|f64)?"
158   "|"
159   /* "23." is a valid floating point number, but "23.e5" and
160      "23.f32" are not.  So, handle the trailing-. case
161      separately.  */
162   "[0-9][0-9_]*\\."
163   "|"
164   /* Finally come integers.
165      subexpression 5: text of integer
166      subexpression 6: if present, type suffix
167      subexpression 7: allows use of alternation, otherwise uninteresting
168   */
169 #define INT_TEXT 5
170 #define INT_TYPE 6
171   "(0x[a-fA-F0-9_]+|0o[0-7_]+|0b[01_]+|[0-9][0-9_]*)"
172   "([iu](size|8|16|32|64))?"
173   ")";
174 /* The number of subexpressions to allocate space for, including the
175    "0th" whole match subexpression.  */
176 #define NUM_SUBEXPRESSIONS 8
177
178 /* The compiled number-matching regex.  */
179
180 static regex_t number_regex;
181
182 /* True if we're running unit tests.  */
183
184 static int unit_testing;
185
186 /* Obstack for data temporarily allocated during parsing.  */
187
188 static struct obstack work_obstack;
189
190 /* Result of parsing.  Points into work_obstack.  */
191
192 static const struct rust_op *rust_ast;
193
194 %}
195
196 %union
197 {
198   /* A typed integer constant.  */
199   struct typed_val_int typed_val_int;
200
201   /* A typed floating point constant.  */
202   struct typed_val_float typed_val_float;
203
204   /* An identifier or string.  */
205   struct stoken sval;
206
207   /* A token representing an opcode, like "==".  */
208   enum exp_opcode opcode;
209
210   /* A list of expressions; for example, the arguments to a function
211      call.  */
212   VEC (rust_op_ptr) **params;
213
214   /* A list of field initializers.  */
215   VEC (set_field) **field_inits;
216
217   /* A single field initializer.  */
218   struct set_field one_field_init;
219
220   /* An expression.  */
221   const struct rust_op *op;
222
223   /* A plain integer, for example used to count the number of
224      "super::" prefixes on a path.  */
225   unsigned int depth;
226 }
227
228 %{
229
230   /* Rust AST operations.  We build a tree of these; then lower them
231      to gdb expressions when parsing has completed.  */
232
233 struct rust_op
234 {
235   /* The opcode.  */
236   enum exp_opcode opcode;
237   /* If OPCODE is OP_TYPE, then this holds information about what type
238      is described by this node.  */
239   enum type_code typecode;
240   /* Indicates whether OPCODE actually represents a compound
241      assignment.  For example, if OPCODE is GTGT and this is false,
242      then this rust_op represents an ordinary ">>"; but if this is
243      true, then this rust_op represents ">>=".  Unused in other
244      cases.  */
245   unsigned int compound_assignment : 1;
246   /* Only used by a field expression; if set, indicates that the field
247      name occurred at the end of the expression and is eligible for
248      completion.  */
249   unsigned int completing : 1;
250   /* Operands of expression.  Which one is used and how depends on the
251      particular opcode.  */
252   RUSTSTYPE left;
253   RUSTSTYPE right;
254 };
255
256 %}
257
258 %token <sval> GDBVAR
259 %token <sval> IDENT
260 %token <sval> COMPLETE
261 %token <typed_val_int> INTEGER
262 %token <typed_val_int> DECIMAL_INTEGER
263 %token <sval> STRING
264 %token <sval> BYTESTRING
265 %token <typed_val_float> FLOAT
266 %token <opcode> COMPOUND_ASSIGN
267
268 /* Keyword tokens.  */
269 %token <voidval> KW_AS
270 %token <voidval> KW_IF
271 %token <voidval> KW_TRUE
272 %token <voidval> KW_FALSE
273 %token <voidval> KW_SUPER
274 %token <voidval> KW_SELF
275 %token <voidval> KW_MUT
276 %token <voidval> KW_EXTERN
277 %token <voidval> KW_CONST
278 %token <voidval> KW_FN
279
280 /* Operator tokens.  */
281 %token <voidval> DOTDOT
282 %token <voidval> OROR
283 %token <voidval> ANDAND
284 %token <voidval> EQEQ
285 %token <voidval> NOTEQ
286 %token <voidval> LTEQ
287 %token <voidval> GTEQ
288 %token <voidval> LSH RSH
289 %token <voidval> COLONCOLON
290 %token <voidval> ARROW
291
292 %type <op> type
293 %type <op> path_for_expr
294 %type <op> identifier_path_for_expr
295 %type <op> path_for_type
296 %type <op> identifier_path_for_type
297 %type <op> just_identifiers_for_type
298
299 %type <params> maybe_type_list
300 %type <params> type_list
301
302 %type <depth> super_path
303
304 %type <op> literal
305 %type <op> expr
306 %type <op> field_expr
307 %type <op> idx_expr
308 %type <op> unop_expr
309 %type <op> binop_expr
310 %type <op> binop_expr_expr
311 %type <op> type_cast_expr
312 %type <op> assignment_expr
313 %type <op> compound_assignment_expr
314 %type <op> paren_expr
315 %type <op> call_expr
316 %type <op> path_expr
317 %type <op> tuple_expr
318 %type <op> unit_expr
319 %type <op> struct_expr
320 %type <op> array_expr
321 %type <op> range_expr
322
323 %type <params> expr_list
324 %type <params> maybe_expr_list
325 %type <params> paren_expr_list
326
327 %type <field_inits> struct_expr_list
328 %type <one_field_init> struct_expr_tail
329
330 /* Precedence.  */
331 %nonassoc DOTDOT
332 %right '=' COMPOUND_ASSIGN
333 %left OROR
334 %left ANDAND
335 %nonassoc EQEQ NOTEQ '<' '>' LTEQ GTEQ
336 %left '|'
337 %left '^'
338 %left '&'
339 %left LSH RSH
340 %left '@'
341 %left '+' '-'
342 %left '*' '/' '%'
343 /* These could be %precedence in Bison, but that isn't a yacc
344    feature.  */
345 %left KW_AS
346 %left UNARY
347 %left '[' '.' '('
348
349 %%
350
351 start:
352         expr
353                 {
354                   /* If we are completing and see a valid parse,
355                      rust_ast will already have been set.  */
356                   if (rust_ast == NULL)
357                     rust_ast = $1;
358                 }
359 ;
360
361 /* Note that the Rust grammar includes a method_call_expr, but we
362    handle this differently, to avoid a shift/reduce conflict with
363    call_expr.  */
364 expr:
365         literal
366 |       path_expr
367 |       tuple_expr
368 |       unit_expr
369 |       struct_expr
370 |       field_expr
371 |       array_expr
372 |       idx_expr
373 |       range_expr
374 |       unop_expr
375 |       binop_expr
376 |       paren_expr
377 |       call_expr
378 ;
379
380 tuple_expr:
381         '(' expr ',' maybe_expr_list ')'
382                 {
383                   VEC_safe_insert (rust_op_ptr, *$4, 0, $2);
384                   error (_("Tuple expressions not supported yet"));
385                 }
386 ;
387
388 unit_expr:
389         '(' ')'
390                 {
391                   struct typed_val_int val;
392
393                   val.type
394                     = language_lookup_primitive_type (parse_language (pstate),
395                                                       parse_gdbarch (pstate),
396                                                       "()");
397                   val.val = 0;
398                   $$ = ast_literal (val);
399                 }
400 ;
401
402 /* To avoid a shift/reduce conflict with call_expr, we don't handle
403    tuple struct expressions here, but instead when examining the
404    AST.  */
405 struct_expr:
406         path_for_expr '{' struct_expr_list '}'
407                 { $$ = ast_struct ($1, $3); }
408 ;
409
410 struct_expr_tail:
411         DOTDOT expr
412                 {
413                   struct set_field sf;
414
415                   sf.name.ptr = NULL;
416                   sf.name.length = 0;
417                   sf.init = $2;
418
419                   $$ = sf;
420                 }
421 |       IDENT ':' expr
422                 {
423                   struct set_field sf;
424
425                   sf.name = $1;
426                   sf.init = $3;
427                   $$ = sf;
428                 }
429 ;
430
431 /* S{} is documented as valid but seems to be an unstable feature, so
432    it is left out here.  */
433 struct_expr_list:
434         struct_expr_tail
435                 {
436                   VEC (set_field) **result
437                     = OBSTACK_ZALLOC (&work_obstack, VEC (set_field) *);
438
439                   make_cleanup (VEC_cleanup (set_field), result);
440                   VEC_safe_push (set_field, *result, &$1);
441
442                   $$ = result;
443                 }
444 |       IDENT ':' expr ',' struct_expr_list
445                 {
446                   struct set_field sf;
447
448                   sf.name = $1;
449                   sf.init = $3;
450                   VEC_safe_push (set_field, *$5, &sf);
451                   $$ = $5;
452                 }
453 ;
454
455 array_expr:
456         '[' KW_MUT expr_list ']'
457                 { $$ = ast_call_ish (OP_ARRAY, NULL, $3); }
458 |       '[' expr_list ']'
459                 { $$ = ast_call_ish (OP_ARRAY, NULL, $2); }
460 |       '[' KW_MUT expr ';' expr ']'
461                 { $$ = ast_operation (OP_RUST_ARRAY, $3, $5); }
462 |       '[' expr ';' expr ']'
463                 { $$ = ast_operation (OP_RUST_ARRAY, $2, $4); }
464 ;
465
466 range_expr:
467         expr DOTDOT
468                 { $$ = ast_range ($1, NULL); }
469 |       expr DOTDOT expr
470                 { $$ = ast_range ($1, $3); }
471 |       DOTDOT expr
472                 { $$ = ast_range (NULL, $2); }
473 |       DOTDOT
474                 { $$ = ast_range (NULL, NULL); }
475 ;
476
477 literal:
478         INTEGER
479                 { $$ = ast_literal ($1); }
480 |       DECIMAL_INTEGER
481                 { $$ = ast_literal ($1); }
482 |       FLOAT
483                 { $$ = ast_dliteral ($1); }
484 |       STRING
485                 {
486                   const struct rust_op *str = ast_string ($1);
487                   VEC (set_field) **fields;
488                   struct set_field field;
489                   struct typed_val_int val;
490                   struct stoken token;
491
492                   fields = OBSTACK_ZALLOC (&work_obstack, VEC (set_field) *);
493                   make_cleanup (VEC_cleanup (set_field), fields);
494
495                   /* Wrap the raw string in the &str struct.  */
496                   field.name.ptr = "data_ptr";
497                   field.name.length = strlen (field.name.ptr);
498                   field.init = ast_unary (UNOP_ADDR, ast_string ($1));
499                   VEC_safe_push (set_field, *fields, &field);
500
501                   val.type = rust_type ("usize");
502                   val.val = $1.length;
503
504                   field.name.ptr = "length";
505                   field.name.length = strlen (field.name.ptr);
506                   field.init = ast_literal (val);
507                   VEC_safe_push (set_field, *fields, &field);
508
509                   token.ptr = "&str";
510                   token.length = strlen (token.ptr);
511                   $$ = ast_struct (ast_path (token, NULL), fields);
512                 }
513 |       BYTESTRING
514                 { $$ = ast_string ($1); }
515 |       KW_TRUE
516                 {
517                   struct typed_val_int val;
518
519                   val.type = language_bool_type (parse_language (pstate),
520                                                  parse_gdbarch (pstate));
521                   val.val = 1;
522                   $$ = ast_literal (val);
523                 }
524 |       KW_FALSE
525                 {
526                   struct typed_val_int val;
527
528                   val.type = language_bool_type (parse_language (pstate),
529                                                  parse_gdbarch (pstate));
530                   val.val = 0;
531                   $$ = ast_literal (val);
532                 }
533 ;
534
535 field_expr:
536         expr '.' IDENT
537                 { $$ = ast_structop ($1, $3.ptr, 0); }
538 |       expr '.' COMPLETE
539                 {
540                   $$ = ast_structop ($1, $3.ptr, 1);
541                   rust_ast = $$;
542                 }
543 |       expr '.' DECIMAL_INTEGER
544                 { $$ = ast_structop_anonymous ($1, $3); }
545 ;
546
547 idx_expr:
548         expr '[' expr ']'
549                 { $$ = ast_operation (BINOP_SUBSCRIPT, $1, $3); }
550 ;
551
552 unop_expr:
553         '+' expr        %prec UNARY
554                 { $$ = ast_unary (UNOP_PLUS, $2); }
555
556 |       '-' expr        %prec UNARY
557                 { $$ = ast_unary (UNOP_NEG, $2); }
558
559 |       '!' expr        %prec UNARY
560                 {
561                   /* Note that we provide a Rust-specific evaluator
562                      override for UNOP_COMPLEMENT, so it can do the
563                      right thing for both bool and integral
564                      values.  */
565                   $$ = ast_unary (UNOP_COMPLEMENT, $2);
566                 }
567
568 |       '*' expr        %prec UNARY
569                 { $$ = ast_unary (UNOP_IND, $2); }
570
571 |       '&' expr        %prec UNARY
572                 { $$ = ast_unary (UNOP_ADDR, $2); }
573
574 |       '&' KW_MUT expr %prec UNARY
575                 { $$ = ast_unary (UNOP_ADDR, $3); }
576
577 ;
578
579 binop_expr:
580         binop_expr_expr
581 |       type_cast_expr
582 |       assignment_expr
583 |       compound_assignment_expr
584 ;
585
586 binop_expr_expr:
587         expr '*' expr
588                 { $$ = ast_operation (BINOP_MUL, $1, $3); }
589
590 |       expr '@' expr
591                 { $$ = ast_operation (BINOP_REPEAT, $1, $3); }
592
593 |       expr '/' expr
594                 { $$ = ast_operation (BINOP_DIV, $1, $3); }
595
596 |       expr '%' expr
597                 { $$ = ast_operation (BINOP_REM, $1, $3); }
598
599 |       expr '<' expr
600                 { $$ = ast_operation (BINOP_LESS, $1, $3); }
601
602 |       expr '>' expr
603                 { $$ = ast_operation (BINOP_GTR, $1, $3); }
604
605 |       expr '&' expr
606                 { $$ = ast_operation (BINOP_BITWISE_AND, $1, $3); }
607
608 |       expr '|' expr
609                 { $$ = ast_operation (BINOP_BITWISE_IOR, $1, $3); }
610
611 |       expr '^' expr
612                 { $$ = ast_operation (BINOP_BITWISE_XOR, $1, $3); }
613
614 |       expr '+' expr
615                 { $$ = ast_operation (BINOP_ADD, $1, $3); }
616
617 |       expr '-' expr
618                 { $$ = ast_operation (BINOP_SUB, $1, $3); }
619
620 |       expr OROR expr
621                 { $$ = ast_operation (BINOP_LOGICAL_OR, $1, $3); }
622
623 |       expr ANDAND expr
624                 { $$ = ast_operation (BINOP_LOGICAL_AND, $1, $3); }
625
626 |       expr EQEQ expr
627                 { $$ = ast_operation (BINOP_EQUAL, $1, $3); }
628
629 |       expr NOTEQ expr
630                 { $$ = ast_operation (BINOP_NOTEQUAL, $1, $3); }
631
632 |       expr LTEQ expr
633                 { $$ = ast_operation (BINOP_LEQ, $1, $3); }
634
635 |       expr GTEQ expr
636                 { $$ = ast_operation (BINOP_GEQ, $1, $3); }
637
638 |       expr LSH expr
639                 { $$ = ast_operation (BINOP_LSH, $1, $3); }
640
641 |       expr RSH expr
642                 { $$ = ast_operation (BINOP_RSH, $1, $3); }
643 ;
644
645 type_cast_expr:
646         expr KW_AS type
647                 { $$ = ast_cast ($1, $3); }
648 ;
649
650 assignment_expr:
651         expr '=' expr
652                 { $$ = ast_operation (BINOP_ASSIGN, $1, $3); }
653 ;
654
655 compound_assignment_expr:
656         expr COMPOUND_ASSIGN expr
657                 { $$ = ast_compound_assignment ($2, $1, $3); }
658
659 ;
660
661 paren_expr:
662         '(' expr ')'
663                 { $$ = $2; }
664 ;
665
666 expr_list:
667         expr
668                 {
669                   $$ = OBSTACK_ZALLOC (&work_obstack, VEC (rust_op_ptr) *);
670                   make_cleanup (VEC_cleanup (rust_op_ptr), $$);
671                   VEC_safe_push (rust_op_ptr, *$$, $1);
672                 }
673 |       expr_list ',' expr
674                 {
675                   VEC_safe_push (rust_op_ptr, *$1, $3);
676                   $$ = $1;
677                 }
678 ;
679
680 maybe_expr_list:
681         /* %empty */
682                 {
683                   /* The result can't be NULL.  */
684                   $$ = OBSTACK_ZALLOC (&work_obstack, VEC (rust_op_ptr) *);
685                   make_cleanup (VEC_cleanup (rust_op_ptr), $$);
686                 }
687 |       expr_list
688                 { $$ = $1; }
689 ;
690
691 paren_expr_list:
692         '('
693         maybe_expr_list
694         ')'
695                 { $$ = $2; }
696 ;
697
698 call_expr:
699         expr paren_expr_list
700                 { $$ = ast_call_ish (OP_FUNCALL, $1, $2); }
701 ;
702
703 maybe_self_path:
704         /* %empty */
705 |       KW_SELF COLONCOLON
706 ;
707
708 super_path:
709         KW_SUPER COLONCOLON
710                 { $$ = 1; }
711 |       super_path KW_SUPER COLONCOLON
712                 { $$ = $1 + 1; }
713 ;
714
715 path_expr:
716         path_for_expr
717                 { $$ = $1; }
718 |       GDBVAR
719                 { $$ = ast_path ($1, NULL); }
720 |       KW_SELF
721                 { $$ = ast_path (make_stoken ("self"), NULL); }
722 ;
723
724 path_for_expr:
725         identifier_path_for_expr
726 |       KW_SELF COLONCOLON identifier_path_for_expr
727                 { $$ = super_name ($3, 0); }
728 |       maybe_self_path super_path identifier_path_for_expr
729                 { $$ = super_name ($3, $2); }
730 |       COLONCOLON identifier_path_for_expr
731                 { $$ = crate_name ($2); }
732 |       KW_EXTERN identifier_path_for_expr
733                 {
734                   /* This is a gdb extension to make it possible to
735                      refer to items in other crates.  It just bypasses
736                      adding the current crate to the front of the
737                      name.  */
738                   $$ = ast_path (rust_concat3 ("::", $2->left.sval.ptr, NULL),
739                                  $2->right.params);
740                 }
741 ;
742
743 identifier_path_for_expr:
744         IDENT
745                 { $$ = ast_path ($1, NULL); }
746 |       identifier_path_for_expr COLONCOLON IDENT
747                 {
748                   $$ = ast_path (rust_concat3 ($1->left.sval.ptr, "::",
749                                                $3.ptr),
750                                  NULL);
751                 }
752 |       identifier_path_for_expr COLONCOLON '<' type_list '>'
753                 { $$ = ast_path ($1->left.sval, $4); }
754 |       identifier_path_for_expr COLONCOLON '<' type_list RSH
755                 {
756                   $$ = ast_path ($1->left.sval, $4);
757                   rust_push_back ('>');
758                 }
759 ;
760
761 path_for_type:
762         identifier_path_for_type
763 |       KW_SELF COLONCOLON identifier_path_for_type
764                 { $$ = super_name ($3, 0); }
765 |       maybe_self_path super_path identifier_path_for_type
766                 { $$ = super_name ($3, $2); }
767 |       COLONCOLON identifier_path_for_type
768                 { $$ = crate_name ($2); }
769 |       KW_EXTERN identifier_path_for_type
770                 {
771                   /* This is a gdb extension to make it possible to
772                      refer to items in other crates.  It just bypasses
773                      adding the current crate to the front of the
774                      name.  */
775                   $$ = ast_path (rust_concat3 ("::", $2->left.sval.ptr, NULL),
776                                  $2->right.params);
777                 }
778 ;
779
780 just_identifiers_for_type:
781         IDENT
782                 { $$ = ast_path ($1, NULL); }
783 |       just_identifiers_for_type COLONCOLON IDENT
784                 {
785                   $$ = ast_path (rust_concat3 ($1->left.sval.ptr, "::",
786                                                $3.ptr),
787                                  NULL);
788                 }
789 ;
790
791 identifier_path_for_type:
792         just_identifiers_for_type
793 |       just_identifiers_for_type '<' type_list '>'
794                 { $$ = ast_path ($1->left.sval, $3); }
795 |       just_identifiers_for_type '<' type_list RSH
796                 {
797                   $$ = ast_path ($1->left.sval, $3);
798                   rust_push_back ('>');
799                 }
800 ;
801
802 type:
803         path_for_type
804 |       '[' type ';' INTEGER ']'
805                 { $$ = ast_array_type ($2, $4); }
806 |       '[' type ';' DECIMAL_INTEGER ']'
807                 { $$ = ast_array_type ($2, $4); }
808 |       '&' '[' type ']'
809                 { $$ = ast_slice_type ($3); }
810 |       '&' type
811                 { $$ = ast_reference_type ($2); }
812 |       '*' KW_MUT type
813                 { $$ = ast_pointer_type ($3, 1); }
814 |       '*' KW_CONST type
815                 { $$ = ast_pointer_type ($3, 0); }
816 |       KW_FN '(' maybe_type_list ')' ARROW type
817                 { $$ = ast_function_type ($6, $3); }
818 |       '(' maybe_type_list ')'
819                 { $$ = ast_tuple_type ($2); }
820 ;
821
822 maybe_type_list:
823         /* %empty */
824                 { $$ = NULL; }
825 |       type_list
826                 { $$ = $1; }
827 ;
828
829 type_list:
830         type
831                 {
832                   VEC (rust_op_ptr) **result
833                     = OBSTACK_ZALLOC (&work_obstack, VEC (rust_op_ptr) *);
834
835                   make_cleanup (VEC_cleanup (rust_op_ptr), result);
836                   VEC_safe_push (rust_op_ptr, *result, $1);
837                   $$ = result;
838                 }
839 |       type_list ',' type
840                 {
841                   VEC_safe_push (rust_op_ptr, *$1, $3);
842                   $$ = $1;
843                 }
844 ;
845
846 %%
847
848 /* A struct of this type is used to describe a token.  */
849
850 struct token_info
851 {
852   const char *name;
853   int value;
854   enum exp_opcode opcode;
855 };
856
857 /* Identifier tokens.  */
858
859 static const struct token_info identifier_tokens[] =
860 {
861   { "as", KW_AS, OP_NULL },
862   { "false", KW_FALSE, OP_NULL },
863   { "if", 0, OP_NULL },
864   { "mut", KW_MUT, OP_NULL },
865   { "const", KW_CONST, OP_NULL },
866   { "self", KW_SELF, OP_NULL },
867   { "super", KW_SUPER, OP_NULL },
868   { "true", KW_TRUE, OP_NULL },
869   { "extern", KW_EXTERN, OP_NULL },
870   { "fn", KW_FN, OP_NULL },
871 };
872
873 /* Operator tokens, sorted longest first.  */
874
875 static const struct token_info operator_tokens[] =
876 {
877   { ">>=", COMPOUND_ASSIGN, BINOP_RSH },
878   { "<<=", COMPOUND_ASSIGN, BINOP_LSH },
879
880   { "<<", LSH, OP_NULL },
881   { ">>", RSH, OP_NULL },
882   { "&&", ANDAND, OP_NULL },
883   { "||", OROR, OP_NULL },
884   { "==", EQEQ, OP_NULL },
885   { "!=", NOTEQ, OP_NULL },
886   { "<=", LTEQ, OP_NULL },
887   { ">=", GTEQ, OP_NULL },
888   { "+=", COMPOUND_ASSIGN, BINOP_ADD },
889   { "-=", COMPOUND_ASSIGN, BINOP_SUB },
890   { "*=", COMPOUND_ASSIGN, BINOP_MUL },
891   { "/=", COMPOUND_ASSIGN, BINOP_DIV },
892   { "%=", COMPOUND_ASSIGN, BINOP_REM },
893   { "&=", COMPOUND_ASSIGN, BINOP_BITWISE_AND },
894   { "|=", COMPOUND_ASSIGN, BINOP_BITWISE_IOR },
895   { "^=", COMPOUND_ASSIGN, BINOP_BITWISE_XOR },
896
897   { "::", COLONCOLON, OP_NULL },
898   { "..", DOTDOT, OP_NULL },
899   { "->", ARROW, OP_NULL }
900 };
901
902 /* Helper function to copy to the name obstack.  */
903
904 static const char *
905 rust_copy_name (const char *name, int len)
906 {
907   return (const char *) obstack_copy0 (&work_obstack, name, len);
908 }
909
910 /* Helper function to make an stoken from a C string.  */
911
912 static struct stoken
913 make_stoken (const char *p)
914 {
915   struct stoken result;
916
917   result.ptr = p;
918   result.length = strlen (result.ptr);
919   return result;
920 }
921
922 /* Helper function to concatenate three strings on the name
923    obstack.  */
924
925 static struct stoken
926 rust_concat3 (const char *s1, const char *s2, const char *s3)
927 {
928   return make_stoken (obconcat (&work_obstack, s1, s2, s3, (char *) NULL));
929 }
930
931 /* Return an AST node referring to NAME, but relative to the crate's
932    name.  */
933
934 static const struct rust_op *
935 crate_name (const struct rust_op *name)
936 {
937   char *crate = rust_crate_for_block (expression_context_block);
938   struct stoken result;
939
940   gdb_assert (name->opcode == OP_VAR_VALUE);
941
942   if (crate == NULL)
943     error (_("Could not find crate for current location"));
944   result = make_stoken (obconcat (&work_obstack, "::", crate, "::",
945                                   name->left.sval.ptr, (char *) NULL));
946   xfree (crate);
947
948   return ast_path (result, name->right.params);
949 }
950
951 /* Create an AST node referring to a "super::" qualified name.  IDENT
952    is the base name and N_SUPERS is how many "super::"s were
953    provided.  N_SUPERS can be zero.  */
954
955 static const struct rust_op *
956 super_name (const struct rust_op *ident, unsigned int n_supers)
957 {
958   const char *scope = block_scope (expression_context_block);
959   int offset;
960
961   gdb_assert (ident->opcode == OP_VAR_VALUE);
962
963   if (scope[0] == '\0')
964     error (_("Couldn't find namespace scope for self::"));
965
966   if (n_supers > 0)
967     {
968       int i;
969       int len;
970       VEC (int) *offsets = NULL;
971       unsigned int current_len, previous_len;
972       struct cleanup *cleanup;
973
974       cleanup = make_cleanup (VEC_cleanup (int), &offsets);
975       current_len = cp_find_first_component (scope);
976       previous_len = 0;
977       while (scope[current_len] != '\0')
978         {
979           VEC_safe_push (int, offsets, current_len);
980           gdb_assert (scope[current_len] == ':');
981           previous_len = current_len;
982           /* The "::".  */
983           current_len += 2;
984           current_len += cp_find_first_component (scope
985                                                   + current_len);
986         }
987
988       len = VEC_length (int, offsets);
989       if (n_supers >= len)
990         error (_("Too many super:: uses from '%s'"), scope);
991
992       offset = VEC_index (int, offsets, len - n_supers);
993
994       do_cleanups (cleanup);
995     }
996   else
997     offset = strlen (scope);
998
999   obstack_grow (&work_obstack, "::", 2);
1000   obstack_grow (&work_obstack, scope, offset);
1001   obstack_grow (&work_obstack, "::", 2);
1002   obstack_grow0 (&work_obstack, ident->left.sval.ptr, ident->left.sval.length);
1003
1004   return ast_path (make_stoken ((const char *) obstack_finish (&work_obstack)),
1005                    ident->right.params);
1006 }
1007
1008 /* A helper that updates innermost_block as appropriate.  */
1009
1010 static void
1011 update_innermost_block (struct block_symbol sym)
1012 {
1013   if (symbol_read_needs_frame (sym.symbol)
1014       && (innermost_block == NULL
1015           || contained_in (sym.block, innermost_block)))
1016     innermost_block = sym.block;
1017 }
1018
1019 /* A helper to look up a Rust type, or fail.  This only works for
1020    types defined by rust_language_arch_info.  */
1021
1022 static struct type *
1023 rust_type (const char *name)
1024 {
1025   struct type *type;
1026
1027   /* When unit testing, we don't bother checking the types, so avoid a
1028      possibly-failing lookup here.  */
1029   if (unit_testing)
1030     return NULL;
1031
1032   type = language_lookup_primitive_type (parse_language (pstate),
1033                                          parse_gdbarch (pstate),
1034                                          name);
1035   if (type == NULL)
1036     error (_("Could not find Rust type %s"), name);
1037   return type;
1038 }
1039
1040 /* Lex a hex number with at least MIN digits and at most MAX
1041    digits.  */
1042
1043 static uint32_t
1044 lex_hex (int min, int max)
1045 {
1046   uint32_t result = 0;
1047   int len = 0;
1048   /* We only want to stop at MAX if we're lexing a byte escape.  */
1049   int check_max = min == max;
1050
1051   while ((check_max ? len <= max : 1)
1052          && ((lexptr[0] >= 'a' && lexptr[0] <= 'f')
1053              || (lexptr[0] >= 'A' && lexptr[0] <= 'F')
1054              || (lexptr[0] >= '0' && lexptr[0] <= '9')))
1055     {
1056       result *= 16;
1057       if (lexptr[0] >= 'a' && lexptr[0] <= 'f')
1058         result = result + 10 + lexptr[0] - 'a';
1059       else if (lexptr[0] >= 'A' && lexptr[0] <= 'F')
1060         result = result + 10 + lexptr[0] - 'A';
1061       else
1062         result = result + lexptr[0] - '0';
1063       ++lexptr;
1064       ++len;
1065     }
1066
1067   if (len < min)
1068     error (_("Not enough hex digits seen"));
1069   if (len > max)
1070     {
1071       gdb_assert (min != max);
1072       error (_("Overlong hex escape"));
1073     }
1074
1075   return result;
1076 }
1077
1078 /* Lex an escape.  IS_BYTE is true if we're lexing a byte escape;
1079    otherwise we're lexing a character escape.  */
1080
1081 static uint32_t
1082 lex_escape (int is_byte)
1083 {
1084   uint32_t result;
1085
1086   gdb_assert (lexptr[0] == '\\');
1087   ++lexptr;
1088   switch (lexptr[0])
1089     {
1090     case 'x':
1091       ++lexptr;
1092       result = lex_hex (2, 2);
1093       break;
1094
1095     case 'u':
1096       if (is_byte)
1097         error (_("Unicode escape in byte literal"));
1098       ++lexptr;
1099       if (lexptr[0] != '{')
1100         error (_("Missing '{' in Unicode escape"));
1101       ++lexptr;
1102       result = lex_hex (1, 6);
1103       /* Could do range checks here.  */
1104       if (lexptr[0] != '}')
1105         error (_("Missing '}' in Unicode escape"));
1106       ++lexptr;
1107       break;
1108
1109     case 'n':
1110       result = '\n';
1111       ++lexptr;
1112       break;
1113     case 'r':
1114       result = '\r';
1115       ++lexptr;
1116       break;
1117     case 't':
1118       result = '\t';
1119       ++lexptr;
1120       break;
1121     case '\\':
1122       result = '\\';
1123       ++lexptr;
1124       break;
1125     case '0':
1126       result = '\0';
1127       ++lexptr;
1128       break;
1129     case '\'':
1130       result = '\'';
1131       ++lexptr;
1132       break;
1133     case '"':
1134       result = '"';
1135       ++lexptr;
1136       break;
1137
1138     default:
1139       error (_("Invalid escape \\%c in literal"), lexptr[0]);
1140     }
1141
1142   return result;
1143 }
1144
1145 /* Lex a character constant.  */
1146
1147 static int
1148 lex_character (void)
1149 {
1150   int is_byte = 0;
1151   uint32_t value;
1152
1153   if (lexptr[0] == 'b')
1154     {
1155       is_byte = 1;
1156       ++lexptr;
1157     }
1158   gdb_assert (lexptr[0] == '\'');
1159   ++lexptr;
1160   /* This should handle UTF-8 here.  */
1161   if (lexptr[0] == '\\')
1162     value = lex_escape (is_byte);
1163   else
1164     {
1165       value = lexptr[0] & 0xff;
1166       ++lexptr;
1167     }
1168
1169   if (lexptr[0] != '\'')
1170     error (_("Unterminated character literal"));
1171   ++lexptr;
1172
1173   rustyylval.typed_val_int.val = value;
1174   rustyylval.typed_val_int.type = rust_type (is_byte ? "u8" : "char");
1175
1176   return INTEGER;
1177 }
1178
1179 /* Return the offset of the double quote if STR looks like the start
1180    of a raw string, or 0 if STR does not start a raw string.  */
1181
1182 static int
1183 starts_raw_string (const char *str)
1184 {
1185   const char *save = str;
1186
1187   if (str[0] != 'r')
1188     return 0;
1189   ++str;
1190   while (str[0] == '#')
1191     ++str;
1192   if (str[0] == '"')
1193     return str - save;
1194   return 0;
1195 }
1196
1197 /* Return true if STR looks like the end of a raw string that had N
1198    hashes at the start.  */
1199
1200 static int
1201 ends_raw_string (const char *str, int n)
1202 {
1203   int i;
1204
1205   gdb_assert (str[0] == '"');
1206   for (i = 0; i < n; ++i)
1207     if (str[i + 1] != '#')
1208       return 0;
1209   return 1;
1210 }
1211
1212 /* Lex a string constant.  */
1213
1214 static int
1215 lex_string (void)
1216 {
1217   int is_byte = lexptr[0] == 'b';
1218   int raw_length;
1219   int len_in_chars = 0;
1220
1221   if (is_byte)
1222     ++lexptr;
1223   raw_length = starts_raw_string (lexptr);
1224   lexptr += raw_length;
1225   gdb_assert (lexptr[0] == '"');
1226   ++lexptr;
1227
1228   while (1)
1229     {
1230       uint32_t value;
1231
1232       if (raw_length > 0)
1233         {
1234           if (lexptr[0] == '"' && ends_raw_string (lexptr, raw_length - 1))
1235             {
1236               /* Exit with lexptr pointing after the final "#".  */
1237               lexptr += raw_length;
1238               break;
1239             }
1240           else if (lexptr[0] == '\0')
1241             error (_("Unexpected EOF in string"));
1242
1243           value = lexptr[0] & 0xff;
1244           if (is_byte && value > 127)
1245             error (_("Non-ASCII value in raw byte string"));
1246           obstack_1grow (&work_obstack, value);
1247
1248           ++lexptr;
1249         }
1250       else if (lexptr[0] == '"')
1251         {
1252           /* Make sure to skip the quote.  */
1253           ++lexptr;
1254           break;
1255         }
1256       else if (lexptr[0] == '\\')
1257         {
1258           value = lex_escape (is_byte);
1259
1260           if (is_byte)
1261             obstack_1grow (&work_obstack, value);
1262           else
1263             convert_between_encodings ("UTF-32", "UTF-8", (gdb_byte *) &value,
1264                                        sizeof (value), sizeof (value),
1265                                        &work_obstack, translit_none);
1266         }
1267       else if (lexptr[0] == '\0')
1268         error (_("Unexpected EOF in string"));
1269       else
1270         {
1271           value = lexptr[0] & 0xff;
1272           if (is_byte && value > 127)
1273             error (_("Non-ASCII value in byte string"));
1274           obstack_1grow (&work_obstack, value);
1275           ++lexptr;
1276         }
1277     }
1278
1279   rustyylval.sval.length = obstack_object_size (&work_obstack);
1280   rustyylval.sval.ptr = (const char *) obstack_finish (&work_obstack);
1281   return is_byte ? BYTESTRING : STRING;
1282 }
1283
1284 /* Return true if STRING starts with whitespace followed by a digit.  */
1285
1286 static int
1287 space_then_number (const char *string)
1288 {
1289   const char *p = string;
1290
1291   while (p[0] == ' ' || p[0] == '\t')
1292     ++p;
1293   if (p == string)
1294     return 0;
1295
1296   return *p >= '0' && *p <= '9';
1297 }
1298
1299 /* Return true if C can start an identifier.  */
1300
1301 static int
1302 rust_identifier_start_p (char c)
1303 {
1304   return ((c >= 'a' && c <= 'z')
1305           || (c >= 'A' && c <= 'Z')
1306           || c == '_'
1307           || c == '$');
1308 }
1309
1310 /* Lex an identifier.  */
1311
1312 static int
1313 lex_identifier (void)
1314 {
1315   const char *start = lexptr;
1316   unsigned int length;
1317   const struct token_info *token;
1318   int i;
1319   int is_gdb_var = lexptr[0] == '$';
1320
1321   gdb_assert (rust_identifier_start_p (lexptr[0]));
1322
1323   ++lexptr;
1324
1325   /* For the time being this doesn't handle Unicode rules.  Non-ASCII
1326      identifiers are gated anyway.  */
1327   while ((lexptr[0] >= 'a' && lexptr[0] <= 'z')
1328          || (lexptr[0] >= 'A' && lexptr[0] <= 'Z')
1329          || lexptr[0] == '_'
1330          || (is_gdb_var && lexptr[0] == '$')
1331          || (lexptr[0] >= '0' && lexptr[0] <= '9'))
1332     ++lexptr;
1333
1334
1335   length = lexptr - start;
1336   token = NULL;
1337   for (i = 0; i < ARRAY_SIZE (identifier_tokens); ++i)
1338     {
1339       if (length == strlen (identifier_tokens[i].name)
1340           && strncmp (identifier_tokens[i].name, start, length) == 0)
1341         {
1342           token = &identifier_tokens[i];
1343           break;
1344         }
1345     }
1346
1347   if (token != NULL)
1348     {
1349       if (token->value == 0)
1350         {
1351           /* Leave the terminating token alone.  */
1352           lexptr = start;
1353           return 0;
1354         }
1355     }
1356   else if (token == NULL
1357            && (strncmp (start, "thread", length) == 0
1358                || strncmp (start, "task", length) == 0)
1359            && space_then_number (lexptr))
1360     {
1361       /* "task" or "thread" followed by a number terminates the
1362          parse, per gdb rules.  */
1363       lexptr = start;
1364       return 0;
1365     }
1366
1367   if (token == NULL || (parse_completion && lexptr[0] == '\0'))
1368     rustyylval.sval = make_stoken (rust_copy_name (start, length));
1369
1370   if (parse_completion && lexptr[0] == '\0')
1371     {
1372       /* Prevent rustyylex from returning two COMPLETE tokens.  */
1373       prev_lexptr = lexptr;
1374       return COMPLETE;
1375     }
1376
1377   if (token != NULL)
1378     return token->value;
1379   if (is_gdb_var)
1380     return GDBVAR;
1381   return IDENT;
1382 }
1383
1384 /* Lex an operator.  */
1385
1386 static int
1387 lex_operator (void)
1388 {
1389   const struct token_info *token = NULL;
1390   int i;
1391
1392   for (i = 0; i < ARRAY_SIZE (operator_tokens); ++i)
1393     {
1394       if (strncmp (operator_tokens[i].name, lexptr,
1395                    strlen (operator_tokens[i].name)) == 0)
1396         {
1397           lexptr += strlen (operator_tokens[i].name);
1398           token = &operator_tokens[i];
1399           break;
1400         }
1401     }
1402
1403   if (token != NULL)
1404     {
1405       rustyylval.opcode = token->opcode;
1406       return token->value;
1407     }
1408
1409   return *lexptr++;
1410 }
1411
1412 /* Lex a number.  */
1413
1414 static int
1415 lex_number (void)
1416 {
1417   regmatch_t subexps[NUM_SUBEXPRESSIONS];
1418   int match;
1419   int is_integer = 0;
1420   int could_be_decimal = 1;
1421   int implicit_i32 = 0;
1422   char *type_name = NULL;
1423   struct type *type;
1424   int end_index;
1425   int type_index = -1;
1426   int i, out;
1427   char *number;
1428   struct cleanup *cleanup = make_cleanup (null_cleanup, NULL);
1429
1430   match = regexec (&number_regex, lexptr, ARRAY_SIZE (subexps), subexps, 0);
1431   /* Failure means the regexp is broken.  */
1432   gdb_assert (match == 0);
1433
1434   if (subexps[INT_TEXT].rm_so != -1)
1435     {
1436       /* Integer part matched.  */
1437       is_integer = 1;
1438       end_index = subexps[INT_TEXT].rm_eo;
1439       if (subexps[INT_TYPE].rm_so == -1)
1440         {
1441           type_name = "i32";
1442           implicit_i32 = 1;
1443         }
1444       else
1445         {
1446           type_index = INT_TYPE;
1447           could_be_decimal = 0;
1448         }
1449     }
1450   else if (subexps[FLOAT_TYPE1].rm_so != -1)
1451     {
1452       /* Found floating point type suffix.  */
1453       end_index = subexps[FLOAT_TYPE1].rm_so;
1454       type_index = FLOAT_TYPE1;
1455     }
1456   else if (subexps[FLOAT_TYPE2].rm_so != -1)
1457     {
1458       /* Found floating point type suffix.  */
1459       end_index = subexps[FLOAT_TYPE2].rm_so;
1460       type_index = FLOAT_TYPE2;
1461     }
1462   else
1463     {
1464       /* Any other floating point match.  */
1465       end_index = subexps[0].rm_eo;
1466       type_name = "f64";
1467     }
1468
1469   /* We need a special case if the final character is ".".  In this
1470      case we might need to parse an integer.  For example, "23.f()" is
1471      a request for a trait method call, not a syntax error involving
1472      the floating point number "23.".  */
1473   gdb_assert (subexps[0].rm_eo > 0);
1474   if (lexptr[subexps[0].rm_eo - 1] == '.')
1475     {
1476       const char *next = skip_spaces_const (&lexptr[subexps[0].rm_eo]);
1477
1478       if (rust_identifier_start_p (*next) || *next == '.')
1479         {
1480           --subexps[0].rm_eo;
1481           is_integer = 1;
1482           end_index = subexps[0].rm_eo;
1483           type_name = "i32";
1484           could_be_decimal = 1;
1485           implicit_i32 = 1;
1486         }
1487     }
1488
1489   /* Compute the type name if we haven't already.  */
1490   if (type_name == NULL)
1491     {
1492       gdb_assert (type_index != -1);
1493       type_name = xstrndup (lexptr + subexps[type_index].rm_so,
1494                            (subexps[type_index].rm_eo
1495                             - subexps[type_index].rm_so));
1496       make_cleanup (xfree, type_name);
1497     }
1498
1499   /* Look up the type.  */
1500   type = rust_type (type_name);
1501
1502   /* Copy the text of the number and remove the "_"s.  */
1503   number = xstrndup (lexptr, end_index);
1504   make_cleanup (xfree, number);
1505   for (i = out = 0; number[i]; ++i)
1506     {
1507       if (number[i] == '_')
1508         could_be_decimal = 0;
1509       else
1510         number[out++] = number[i];
1511     }
1512   number[out] = '\0';
1513
1514   /* Advance past the match.  */
1515   lexptr += subexps[0].rm_eo;
1516
1517   /* Parse the number.  */
1518   if (is_integer)
1519     {
1520       uint64_t value;
1521       int radix = 10;
1522       if (number[0] == '0')
1523         {
1524           if (number[1] == 'x')
1525             radix = 16;
1526           else if (number[1] == 'o')
1527             radix = 8;
1528           else if (number[1] == 'b')
1529             radix = 2;
1530           if (radix != 10)
1531             {
1532               number += 2;
1533               could_be_decimal = 0;
1534             }
1535         }
1536
1537       value = strtoul (number, NULL, radix);
1538       if (implicit_i32 && value >= ((uint64_t) 1) << 31)
1539         type = rust_type ("i64");
1540
1541       rustyylval.typed_val_int.val = value;
1542       rustyylval.typed_val_int.type = type;
1543     }
1544   else
1545     {
1546       rustyylval.typed_val_float.dval = strtod (number, NULL);
1547       rustyylval.typed_val_float.type = type;
1548     }
1549
1550   do_cleanups (cleanup);
1551   return is_integer ? (could_be_decimal ? DECIMAL_INTEGER : INTEGER) : FLOAT;
1552 }
1553
1554 /* The lexer.  */
1555
1556 static int
1557 rustyylex (void)
1558 {
1559   /* Skip all leading whitespace.  */
1560   while (lexptr[0] == ' ' || lexptr[0] == '\t' || lexptr[0] == '\r'
1561          || lexptr[0] == '\n')
1562     ++lexptr;
1563
1564   /* If we hit EOF and we're completing, then return COMPLETE -- maybe
1565      we're completing an empty string at the end of a field_expr.
1566      But, we don't want to return two COMPLETE tokens in a row.  */
1567   if (lexptr[0] == '\0' && lexptr == prev_lexptr)
1568     return 0;
1569   prev_lexptr = lexptr;
1570   if (lexptr[0] == '\0')
1571     {
1572       if (parse_completion)
1573         {
1574           rustyylval.sval = make_stoken ("");
1575           return COMPLETE;
1576         }
1577       return 0;
1578     }
1579
1580   if (lexptr[0] >= '0' && lexptr[0] <= '9')
1581     return lex_number ();
1582   else if (lexptr[0] == 'b' && lexptr[1] == '\'')
1583     return lex_character ();
1584   else if (lexptr[0] == 'b' && lexptr[1] == '"')
1585     return lex_string ();
1586   else if (lexptr[0] == 'b' && starts_raw_string (lexptr + 1))
1587     return lex_string ();
1588   else if (starts_raw_string (lexptr))
1589     return lex_string ();
1590   else if (rust_identifier_start_p (lexptr[0]))
1591     return lex_identifier ();
1592   else if (lexptr[0] == '"')
1593     return lex_string ();
1594   else if (lexptr[0] == '\'')
1595     return lex_character ();
1596   else if (lexptr[0] == '}' || lexptr[0] == ']')
1597     {
1598       /* Falls through to lex_operator.  */
1599       --paren_depth;
1600     }
1601   else if (lexptr[0] == '(' || lexptr[0] == '{')
1602     {
1603       /* Falls through to lex_operator.  */
1604       ++paren_depth;
1605     }
1606   else if (lexptr[0] == ',' && comma_terminates && paren_depth == 0)
1607     return 0;
1608
1609   return lex_operator ();
1610 }
1611
1612 /* Push back a single character to be re-lexed.  */
1613
1614 static void
1615 rust_push_back (char c)
1616 {
1617   /* Can't be called before any lexing.  */
1618   gdb_assert (prev_lexptr != NULL);
1619
1620   --lexptr;
1621   gdb_assert (*lexptr == c);
1622 }
1623
1624 \f
1625
1626 /* Make an arbitrary operation and fill in the fields.  */
1627
1628 static const struct rust_op *
1629 ast_operation (enum exp_opcode opcode, const struct rust_op *left,
1630                 const struct rust_op *right)
1631 {
1632   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1633
1634   result->opcode = opcode;
1635   result->left.op = left;
1636   result->right.op = right;
1637
1638   return result;
1639 }
1640
1641 /* Make a compound assignment operation.  */
1642
1643 static const struct rust_op *
1644 ast_compound_assignment (enum exp_opcode opcode, const struct rust_op *left,
1645                           const struct rust_op *right)
1646 {
1647   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1648
1649   result->opcode = opcode;
1650   result->compound_assignment = 1;
1651   result->left.op = left;
1652   result->right.op = right;
1653
1654   return result;
1655 }
1656
1657 /* Make a typed integer literal operation.  */
1658
1659 static const struct rust_op *
1660 ast_literal (struct typed_val_int val)
1661 {
1662   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1663
1664   result->opcode = OP_LONG;
1665   result->left.typed_val_int = val;
1666
1667   return result;
1668 }
1669
1670 /* Make a typed floating point literal operation.  */
1671
1672 static const struct rust_op *
1673 ast_dliteral (struct typed_val_float val)
1674 {
1675   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1676
1677   result->opcode = OP_DOUBLE;
1678   result->left.typed_val_float = val;
1679
1680   return result;
1681 }
1682
1683 /* Make a unary operation.  */
1684
1685 static const struct rust_op *
1686 ast_unary (enum exp_opcode opcode, const struct rust_op *expr)
1687 {
1688   return ast_operation (opcode, expr, NULL);
1689 }
1690
1691 /* Make a cast operation.  */
1692
1693 static const struct rust_op *
1694 ast_cast (const struct rust_op *expr, const struct rust_op *type)
1695 {
1696   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1697
1698   result->opcode = UNOP_CAST;
1699   result->left.op = expr;
1700   result->right.op = type;
1701
1702   return result;
1703 }
1704
1705 /* Make a call-like operation.  This is nominally a function call, but
1706    when lowering we may discover that it actually represents the
1707    creation of a tuple struct.  */
1708
1709 static const struct rust_op *
1710 ast_call_ish (enum exp_opcode opcode, const struct rust_op *expr,
1711                VEC (rust_op_ptr) **params)
1712 {
1713   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1714
1715   result->opcode = opcode;
1716   result->left.op = expr;
1717   result->right.params = params;
1718
1719   return result;
1720 }
1721
1722 /* Make a structure creation operation.  */
1723
1724 static const struct rust_op *
1725 ast_struct (const struct rust_op *name, VEC (set_field) **fields)
1726 {
1727   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1728
1729   result->opcode = OP_AGGREGATE;
1730   result->left.op = name;
1731   result->right.field_inits = fields;
1732
1733   return result;
1734 }
1735
1736 /* Make an identifier path.  */
1737
1738 static const struct rust_op *
1739 ast_path (struct stoken path, VEC (rust_op_ptr) **params)
1740 {
1741   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1742
1743   result->opcode = OP_VAR_VALUE;
1744   result->left.sval = path;
1745   result->right.params = params;
1746
1747   return result;
1748 }
1749
1750 /* Make a string constant operation.  */
1751
1752 static const struct rust_op *
1753 ast_string (struct stoken str)
1754 {
1755   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1756
1757   result->opcode = OP_STRING;
1758   result->left.sval = str;
1759
1760   return result;
1761 }
1762
1763 /* Make a field expression.  */
1764
1765 static const struct rust_op *
1766 ast_structop (const struct rust_op *left, const char *name, int completing)
1767 {
1768   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1769
1770   result->opcode = STRUCTOP_STRUCT;
1771   result->completing = completing;
1772   result->left.op = left;
1773   result->right.sval = make_stoken (name);
1774
1775   return result;
1776 }
1777
1778 /* Make an anonymous struct operation, like 'x.0'.  */
1779
1780 static const struct rust_op *
1781 ast_structop_anonymous (const struct rust_op *left,
1782                          struct typed_val_int number)
1783 {
1784   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1785
1786   result->opcode = STRUCTOP_ANONYMOUS;
1787   result->left.op = left;
1788   result->right.typed_val_int = number;
1789
1790   return result;
1791 }
1792
1793 /* Make a range operation.  */
1794
1795 static const struct rust_op *
1796 ast_range (const struct rust_op *lhs, const struct rust_op *rhs)
1797 {
1798   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1799
1800   result->opcode = OP_RANGE;
1801   result->left.op = lhs;
1802   result->right.op = rhs;
1803
1804   return result;
1805 }
1806
1807 /* A helper function to make a type-related AST node.  */
1808
1809 static struct rust_op *
1810 ast_basic_type (enum type_code typecode)
1811 {
1812   struct rust_op *result = OBSTACK_ZALLOC (&work_obstack, struct rust_op);
1813
1814   result->opcode = OP_TYPE;
1815   result->typecode = typecode;
1816   return result;
1817 }
1818
1819 /* Create an AST node describing an array type.  */
1820
1821 static const struct rust_op *
1822 ast_array_type (const struct rust_op *lhs, struct typed_val_int val)
1823 {
1824   struct rust_op *result = ast_basic_type (TYPE_CODE_ARRAY);
1825
1826   result->left.op = lhs;
1827   result->right.typed_val_int = val;
1828   return result;
1829 }
1830
1831 /* Create an AST node describing a reference type.  */
1832
1833 static const struct rust_op *
1834 ast_slice_type (const struct rust_op *type)
1835 {
1836   /* Use TYPE_CODE_COMPLEX just because it is handy.  */
1837   struct rust_op *result = ast_basic_type (TYPE_CODE_COMPLEX);
1838
1839   result->left.op = type;
1840   return result;
1841 }
1842
1843 /* Create an AST node describing a reference type.  */
1844
1845 static const struct rust_op *
1846 ast_reference_type (const struct rust_op *type)
1847 {
1848   struct rust_op *result = ast_basic_type (TYPE_CODE_REF);
1849
1850   result->left.op = type;
1851   return result;
1852 }
1853
1854 /* Create an AST node describing a pointer type.  */
1855
1856 static const struct rust_op *
1857 ast_pointer_type (const struct rust_op *type, int is_mut)
1858 {
1859   struct rust_op *result = ast_basic_type (TYPE_CODE_PTR);
1860
1861   result->left.op = type;
1862   /* For the time being we ignore is_mut.  */
1863   return result;
1864 }
1865
1866 /* Create an AST node describing a function type.  */
1867
1868 static const struct rust_op *
1869 ast_function_type (const struct rust_op *rtype, VEC (rust_op_ptr) **params)
1870 {
1871   struct rust_op *result = ast_basic_type (TYPE_CODE_FUNC);
1872
1873   result->left.op = rtype;
1874   result->right.params = params;
1875   return result;
1876 }
1877
1878 /* Create an AST node describing a tuple type.  */
1879
1880 static const struct rust_op *
1881 ast_tuple_type (VEC (rust_op_ptr) **params)
1882 {
1883   struct rust_op *result = ast_basic_type (TYPE_CODE_STRUCT);
1884
1885   result->left.params = params;
1886   return result;
1887 }
1888
1889 /* A helper to appropriately munge NAME and BLOCK depending on the
1890    presence of a leading "::".  */
1891
1892 static void
1893 munge_name_and_block (const char **name, const struct block **block)
1894 {
1895   /* If it is a global reference, skip the current block in favor of
1896      the static block.  */
1897   if (strncmp (*name, "::", 2) == 0)
1898     {
1899       *name += 2;
1900       *block = block_static_block (*block);
1901     }
1902 }
1903
1904 /* Like lookup_symbol, but handles Rust namespace conventions, and
1905    doesn't require field_of_this_result.  */
1906
1907 static struct block_symbol
1908 rust_lookup_symbol (const char *name, const struct block *block,
1909                     const domain_enum domain)
1910 {
1911   struct block_symbol result;
1912
1913   munge_name_and_block (&name, &block);
1914
1915   result = lookup_symbol (name, block, domain, NULL);
1916   if (result.symbol != NULL)
1917     update_innermost_block (result);
1918   return result;
1919 }
1920
1921 /* Look up a type, following Rust namespace conventions.  */
1922
1923 static struct type *
1924 rust_lookup_type (const char *name, const struct block *block)
1925 {
1926   struct block_symbol result;
1927   struct type *type;
1928
1929   munge_name_and_block (&name, &block);
1930
1931   result = lookup_symbol (name, block, STRUCT_DOMAIN, NULL);
1932   if (result.symbol != NULL)
1933     {
1934       update_innermost_block (result);
1935       return SYMBOL_TYPE (result.symbol);
1936     }
1937
1938   type = lookup_typename (parse_language (pstate), parse_gdbarch (pstate),
1939                           name, NULL, 1);
1940   if (type != NULL)
1941     return type;
1942
1943   /* Last chance, try a built-in type.  */
1944   return language_lookup_primitive_type (parse_language (pstate),
1945                                          parse_gdbarch (pstate),
1946                                          name);
1947 }
1948
1949 static struct type *convert_ast_to_type (struct parser_state *state,
1950                                          const struct rust_op *operation);
1951 static const char *convert_name (struct parser_state *state,
1952                                  const struct rust_op *operation);
1953
1954 /* Convert a vector of rust_ops representing types to a vector of
1955    types.  */
1956
1957 static VEC (type_ptr) *
1958 convert_params_to_types (struct parser_state *state, VEC (rust_op_ptr) *params)
1959 {
1960   int i;
1961   const struct rust_op *op;
1962   VEC (type_ptr) *result = NULL;
1963   struct cleanup *cleanup = make_cleanup (VEC_cleanup (type_ptr), &result);
1964
1965   for (i = 0; VEC_iterate (rust_op_ptr, params, i, op); ++i)
1966     VEC_safe_push (type_ptr, result, convert_ast_to_type (state, op));
1967
1968   discard_cleanups (cleanup);
1969   return result;
1970 }
1971
1972 /* Convert a rust_op representing a type to a struct type *.  */
1973
1974 static struct type *
1975 convert_ast_to_type (struct parser_state *state,
1976                      const struct rust_op *operation)
1977 {
1978   struct type *type, *result = NULL;
1979
1980   if (operation->opcode == OP_VAR_VALUE)
1981     {
1982       const char *varname = convert_name (state, operation);
1983
1984       result = rust_lookup_type (varname, expression_context_block);
1985       if (result == NULL)
1986         error (_("No typed name '%s' in current context"), varname);
1987       return result;
1988     }
1989
1990   gdb_assert (operation->opcode == OP_TYPE);
1991
1992   switch (operation->typecode)
1993     {
1994     case TYPE_CODE_ARRAY:
1995       type = convert_ast_to_type (state, operation->left.op);
1996       if (operation->right.typed_val_int.val < 0)
1997         error (_("Negative array length"));
1998       result = lookup_array_range_type (type, 0,
1999                                         operation->right.typed_val_int.val - 1);
2000       break;
2001
2002     case TYPE_CODE_COMPLEX:
2003       {
2004         struct type *usize = rust_type ("usize");
2005
2006         type = convert_ast_to_type (state, operation->left.op);
2007         result = rust_slice_type ("&[*gdb*]", type, usize);
2008       }
2009       break;
2010
2011     case TYPE_CODE_REF:
2012     case TYPE_CODE_PTR:
2013       /* For now we treat &x and *x identically.  */
2014       type = convert_ast_to_type (state, operation->left.op);
2015       result = lookup_pointer_type (type);
2016       break;
2017
2018     case TYPE_CODE_FUNC:
2019       {
2020         VEC (type_ptr) *args
2021           = convert_params_to_types (state, *operation->right.params);
2022         struct cleanup *cleanup
2023           = make_cleanup (VEC_cleanup (type_ptr), &args);
2024         struct type **argtypes = NULL;
2025
2026         type = convert_ast_to_type (state, operation->left.op);
2027         if (!VEC_empty (type_ptr, args))
2028           argtypes = VEC_address (type_ptr, args);
2029
2030         result
2031           = lookup_function_type_with_arguments (type,
2032                                                  VEC_length (type_ptr, args),
2033                                                  argtypes);
2034         result = lookup_pointer_type (result);
2035
2036         do_cleanups (cleanup);
2037       }
2038       break;
2039
2040     case TYPE_CODE_STRUCT:
2041       {
2042         VEC (type_ptr) *args
2043           = convert_params_to_types (state, *operation->left.params);
2044         struct cleanup *cleanup
2045           = make_cleanup (VEC_cleanup (type_ptr), &args);
2046         int i;
2047         struct type *type;
2048         const char *name;
2049
2050         obstack_1grow (&work_obstack, '(');
2051         for (i = 0; VEC_iterate (type_ptr, args, i, type); ++i)
2052           {
2053             char *type_name = type_to_string (type);
2054
2055             if (i > 0)
2056               obstack_1grow (&work_obstack, ',');
2057             obstack_grow_str (&work_obstack, type_name);
2058
2059             xfree (type_name);
2060           }
2061
2062         obstack_grow_str0 (&work_obstack, ")");
2063         name = (const char *) obstack_finish (&work_obstack);
2064
2065         /* We don't allow creating new tuple types (yet), but we do
2066            allow looking up existing tuple types.  */
2067         result = rust_lookup_type (name, expression_context_block);
2068         if (result == NULL)
2069           error (_("could not find tuple type '%s'"), name);
2070
2071         do_cleanups (cleanup);
2072       }
2073       break;
2074
2075     default:
2076       gdb_assert_not_reached ("unhandled opcode in convert_ast_to_type");
2077     }
2078
2079   gdb_assert (result != NULL);
2080   return result;
2081 }
2082
2083 /* A helper function to turn a rust_op representing a name into a full
2084    name.  This applies generic arguments as needed.  The returned name
2085    is allocated on the work obstack.  */
2086
2087 static const char *
2088 convert_name (struct parser_state *state, const struct rust_op *operation)
2089 {
2090   VEC (type_ptr) *types;
2091   struct cleanup *cleanup;
2092   int i;
2093   struct type *type;
2094
2095   gdb_assert (operation->opcode == OP_VAR_VALUE);
2096
2097   if (operation->right.params == NULL)
2098     return operation->left.sval.ptr;
2099
2100   types = convert_params_to_types (state, *operation->right.params);
2101   cleanup = make_cleanup (VEC_cleanup (type_ptr), &types);
2102
2103   obstack_grow_str (&work_obstack, operation->left.sval.ptr);
2104   obstack_1grow (&work_obstack, '<');
2105   for (i = 0; VEC_iterate (type_ptr, types, i, type); ++i)
2106     {
2107       char *type_name = type_to_string (type);
2108
2109       if (i > 0)
2110         obstack_1grow (&work_obstack, ',');
2111
2112       obstack_grow_str (&work_obstack, type_name);
2113       xfree (type_name);
2114     }
2115   obstack_grow_str0 (&work_obstack, ">");
2116
2117   do_cleanups (cleanup);
2118
2119   return (const char *) obstack_finish (&work_obstack);
2120 }
2121
2122 static void convert_ast_to_expression (struct parser_state *state,
2123                                        const struct rust_op *operation,
2124                                        const struct rust_op *top);
2125
2126 /* A helper function that converts a vec of rust_ops to a gdb
2127    expression.  */
2128
2129 static void
2130 convert_params_to_expression (struct parser_state *state,
2131                               VEC (rust_op_ptr) *params,
2132                               const struct rust_op *top)
2133 {
2134   int i;
2135   rust_op_ptr elem;
2136
2137   for (i = 0; VEC_iterate (rust_op_ptr, params, i, elem); ++i)
2138     convert_ast_to_expression (state, elem, top);
2139 }
2140
2141 /* Lower a rust_op to a gdb expression.  STATE is the parser state.
2142    OPERATION is the operation to lower.  TOP is a pointer to the
2143    top-most operation; it is used to handle the special case where the
2144    top-most expression is an identifier and can be optionally lowered
2145    to OP_TYPE.  */
2146
2147 static void
2148 convert_ast_to_expression (struct parser_state *state,
2149                            const struct rust_op *operation,
2150                            const struct rust_op *top)
2151 {
2152   switch (operation->opcode)
2153     {
2154     case OP_LONG:
2155       write_exp_elt_opcode (state, OP_LONG);
2156       write_exp_elt_type (state, operation->left.typed_val_int.type);
2157       write_exp_elt_longcst (state, operation->left.typed_val_int.val);
2158       write_exp_elt_opcode (state, OP_LONG);
2159       break;
2160
2161     case OP_DOUBLE:
2162       write_exp_elt_opcode (state, OP_DOUBLE);
2163       write_exp_elt_type (state, operation->left.typed_val_float.type);
2164       write_exp_elt_dblcst (state, operation->left.typed_val_float.dval);
2165       write_exp_elt_opcode (state, OP_DOUBLE);
2166       break;
2167
2168     case STRUCTOP_STRUCT:
2169       {
2170         convert_ast_to_expression (state, operation->left.op, top);
2171
2172         if (operation->completing)
2173           mark_struct_expression (state);
2174         write_exp_elt_opcode (state, STRUCTOP_STRUCT);
2175         write_exp_string (state, operation->right.sval);
2176         write_exp_elt_opcode (state, STRUCTOP_STRUCT);
2177       }
2178       break;
2179
2180     case STRUCTOP_ANONYMOUS:
2181       {
2182         convert_ast_to_expression (state, operation->left.op, top);
2183
2184         write_exp_elt_opcode (state, STRUCTOP_ANONYMOUS);
2185         write_exp_elt_longcst (state, operation->right.typed_val_int.val);
2186         write_exp_elt_opcode (state, STRUCTOP_ANONYMOUS);
2187       }
2188       break;
2189
2190     case UNOP_PLUS:
2191     case UNOP_NEG:
2192     case UNOP_COMPLEMENT:
2193     case UNOP_IND:
2194     case UNOP_ADDR:
2195       convert_ast_to_expression (state, operation->left.op, top);
2196       write_exp_elt_opcode (state, operation->opcode);
2197       break;
2198
2199     case BINOP_SUBSCRIPT:
2200     case BINOP_MUL:
2201     case BINOP_REPEAT:
2202     case BINOP_DIV:
2203     case BINOP_REM:
2204     case BINOP_LESS:
2205     case BINOP_GTR:
2206     case BINOP_BITWISE_AND:
2207     case BINOP_BITWISE_IOR:
2208     case BINOP_BITWISE_XOR:
2209     case BINOP_ADD:
2210     case BINOP_SUB:
2211     case BINOP_LOGICAL_OR:
2212     case BINOP_LOGICAL_AND:
2213     case BINOP_EQUAL:
2214     case BINOP_NOTEQUAL:
2215     case BINOP_LEQ:
2216     case BINOP_GEQ:
2217     case BINOP_LSH:
2218     case BINOP_RSH:
2219     case BINOP_ASSIGN:
2220     case OP_RUST_ARRAY:
2221       convert_ast_to_expression (state, operation->left.op, top);
2222       convert_ast_to_expression (state, operation->right.op, top);
2223       if (operation->compound_assignment)
2224         {
2225           write_exp_elt_opcode (state, BINOP_ASSIGN_MODIFY);
2226           write_exp_elt_opcode (state, operation->opcode);
2227           write_exp_elt_opcode (state, BINOP_ASSIGN_MODIFY);
2228         }
2229       else
2230         write_exp_elt_opcode (state, operation->opcode);
2231
2232       if (operation->compound_assignment
2233           || operation->opcode == BINOP_ASSIGN)
2234         {
2235           struct type *type;
2236
2237           type = language_lookup_primitive_type (parse_language (state),
2238                                                  parse_gdbarch (state),
2239                                                  "()");
2240
2241           write_exp_elt_opcode (state, OP_LONG);
2242           write_exp_elt_type (state, type);
2243           write_exp_elt_longcst (state, 0);
2244           write_exp_elt_opcode (state, OP_LONG);
2245
2246           write_exp_elt_opcode (state, BINOP_COMMA);
2247         }
2248       break;
2249
2250     case UNOP_CAST:
2251       {
2252         struct type *type = convert_ast_to_type (state, operation->right.op);
2253
2254         convert_ast_to_expression (state, operation->left.op, top);
2255         write_exp_elt_opcode (state, UNOP_CAST);
2256         write_exp_elt_type (state, type);
2257         write_exp_elt_opcode (state, UNOP_CAST);
2258       }
2259       break;
2260
2261     case OP_FUNCALL:
2262       {
2263         if (operation->left.op->opcode == OP_VAR_VALUE)
2264           {
2265             struct type *type;
2266             const char *varname = convert_name (state, operation->left.op);
2267
2268             type = rust_lookup_type (varname, expression_context_block);
2269             if (type != NULL)
2270               {
2271                 /* This is actually a tuple struct expression, not a
2272                    call expression.  */
2273                 rust_op_ptr elem;
2274                 int i;
2275                 VEC (rust_op_ptr) *params = *operation->right.params;
2276
2277                 if (TYPE_CODE (type) != TYPE_CODE_NAMESPACE)
2278                   {
2279                     if (!rust_tuple_struct_type_p (type))
2280                       error (_("Type %s is not a tuple struct"), varname);
2281
2282                     for (i = 0;
2283                          VEC_iterate (rust_op_ptr, params, i, elem);
2284                          ++i)
2285                       {
2286                         char *cell = get_print_cell ();
2287
2288                         xsnprintf (cell, PRINT_CELL_SIZE, "__%d", i);
2289                         write_exp_elt_opcode (state, OP_NAME);
2290                         write_exp_string (state, make_stoken (cell));
2291                         write_exp_elt_opcode (state, OP_NAME);
2292
2293                         convert_ast_to_expression (state, elem, top);
2294                       }
2295
2296                     write_exp_elt_opcode (state, OP_AGGREGATE);
2297                     write_exp_elt_type (state, type);
2298                     write_exp_elt_longcst (state,
2299                                            2 * VEC_length (rust_op_ptr,
2300                                                            params));
2301                     write_exp_elt_opcode (state, OP_AGGREGATE);
2302                     break;
2303                   }
2304               }
2305           }
2306         convert_ast_to_expression (state, operation->left.op, top);
2307         convert_params_to_expression (state, *operation->right.params, top);
2308         write_exp_elt_opcode (state, OP_FUNCALL);
2309         write_exp_elt_longcst (state, VEC_length (rust_op_ptr,
2310                                                   *operation->right.params));
2311         write_exp_elt_longcst (state, OP_FUNCALL);
2312       }
2313       break;
2314
2315     case OP_ARRAY:
2316       gdb_assert (operation->left.op == NULL);
2317       convert_params_to_expression (state, *operation->right.params, top);
2318       write_exp_elt_opcode (state, OP_ARRAY);
2319       write_exp_elt_longcst (state, 0);
2320       write_exp_elt_longcst (state, VEC_length (rust_op_ptr,
2321                                                 *operation->right.params) - 1);
2322       write_exp_elt_longcst (state, OP_ARRAY);
2323       break;
2324
2325     case OP_VAR_VALUE:
2326       {
2327         struct block_symbol sym;
2328         const char *varname;
2329
2330         if (operation->left.sval.ptr[0] == '$')
2331           {
2332             write_dollar_variable (state, operation->left.sval);
2333             break;
2334           }
2335
2336         varname = convert_name (state, operation);
2337         sym = rust_lookup_symbol (varname, expression_context_block,
2338                                   VAR_DOMAIN);
2339         if (sym.symbol != NULL)
2340           {
2341             write_exp_elt_opcode (state, OP_VAR_VALUE);
2342             write_exp_elt_block (state, sym.block);
2343             write_exp_elt_sym (state, sym.symbol);
2344             write_exp_elt_opcode (state, OP_VAR_VALUE);
2345           }
2346         else
2347           {
2348             struct type *type;
2349
2350             type = rust_lookup_type (varname, expression_context_block);
2351             if (type == NULL)
2352               error (_("No symbol '%s' in current context"), varname);
2353
2354             if (TYPE_CODE (type) == TYPE_CODE_STRUCT
2355                 && TYPE_NFIELDS (type) == 0)
2356               {
2357                 /* A unit-like struct.  */
2358                 write_exp_elt_opcode (state, OP_AGGREGATE);
2359                 write_exp_elt_type (state, type);
2360                 write_exp_elt_longcst (state, 0);
2361                 write_exp_elt_opcode (state, OP_AGGREGATE);
2362               }
2363             else if (operation == top)
2364               {
2365                 write_exp_elt_opcode (state, OP_TYPE);
2366                 write_exp_elt_type (state, type);
2367                 write_exp_elt_opcode (state, OP_TYPE);
2368                 break;
2369               }
2370           }
2371       }
2372       break;
2373
2374     case OP_AGGREGATE:
2375       {
2376         int i;
2377         int length;
2378         struct set_field *init;
2379         VEC (set_field) *fields = *operation->right.field_inits;
2380         struct type *type;
2381         const char *name;
2382
2383         length = 0;
2384         for (i = 0; VEC_iterate (set_field, fields, i, init); ++i)
2385           {
2386             if (init->name.ptr != NULL)
2387               {
2388                 write_exp_elt_opcode (state, OP_NAME);
2389                 write_exp_string (state, init->name);
2390                 write_exp_elt_opcode (state, OP_NAME);
2391                 ++length;
2392               }
2393
2394             convert_ast_to_expression (state, init->init, top);
2395             ++length;
2396
2397             if (init->name.ptr == NULL)
2398               {
2399                 /* This is handled differently from Ada in our
2400                    evaluator.  */
2401                 write_exp_elt_opcode (state, OP_OTHERS);
2402               }
2403           }
2404
2405         name = convert_name (state, operation->left.op);
2406         type = rust_lookup_type (name, expression_context_block);
2407         if (type == NULL)
2408           error (_("Could not find type '%s'"), operation->left.sval.ptr);
2409
2410         if (TYPE_CODE (type) != TYPE_CODE_STRUCT
2411             || rust_tuple_type_p (type)
2412             || rust_tuple_struct_type_p (type))
2413           error (_("Struct expression applied to non-struct type"));
2414
2415         write_exp_elt_opcode (state, OP_AGGREGATE);
2416         write_exp_elt_type (state, type);
2417         write_exp_elt_longcst (state, length);
2418         write_exp_elt_opcode (state, OP_AGGREGATE);
2419       }
2420       break;
2421
2422     case OP_STRING:
2423       {
2424         write_exp_elt_opcode (state, OP_STRING);
2425         write_exp_string (state, operation->left.sval);
2426         write_exp_elt_opcode (state, OP_STRING);
2427       }
2428       break;
2429
2430     case OP_RANGE:
2431       {
2432         enum range_type kind = BOTH_BOUND_DEFAULT;
2433
2434         if (operation->left.op != NULL)
2435           {
2436             convert_ast_to_expression (state, operation->left.op, top);
2437             kind = HIGH_BOUND_DEFAULT;
2438           }
2439         if (operation->right.op != NULL)
2440           {
2441             convert_ast_to_expression (state, operation->right.op, top);
2442             if (kind == BOTH_BOUND_DEFAULT)
2443               kind = LOW_BOUND_DEFAULT;
2444             else
2445               {
2446                 gdb_assert (kind == HIGH_BOUND_DEFAULT);
2447                 kind = NONE_BOUND_DEFAULT;
2448               }
2449           }
2450         write_exp_elt_opcode (state, OP_RANGE);
2451         write_exp_elt_longcst (state, kind);
2452         write_exp_elt_opcode (state, OP_RANGE);
2453       }
2454       break;
2455
2456     default:
2457       gdb_assert_not_reached ("unhandled opcode in convert_ast_to_expression");
2458     }
2459 }
2460
2461 \f
2462
2463 /* The parser as exposed to gdb.  */
2464
2465 int
2466 rust_parse (struct parser_state *state)
2467 {
2468   int result;
2469   struct cleanup *cleanup;
2470
2471   obstack_init (&work_obstack);
2472   cleanup = make_cleanup_obstack_free (&work_obstack);
2473   rust_ast = NULL;
2474
2475   pstate = state;
2476   result = rustyyparse ();
2477
2478   if (!result || (parse_completion && rust_ast != NULL))
2479     {
2480       const struct rust_op *ast = rust_ast;
2481
2482       rust_ast = NULL;
2483       gdb_assert (ast != NULL);
2484       convert_ast_to_expression (state, ast, ast);
2485     }
2486
2487   do_cleanups (cleanup);
2488   return result;
2489 }
2490
2491 /* The parser error handler.  */
2492
2493 void
2494 rustyyerror (char *msg)
2495 {
2496   const char *where = prev_lexptr ? prev_lexptr : lexptr;
2497   error (_("%s in expression, near `%s'."), (msg ? msg : "Error"), where);
2498 }
2499
2500 \f
2501
2502 #if GDB_SELF_TEST
2503
2504 /* Initialize the lexer for testing.  */
2505
2506 static void
2507 rust_lex_test_init (const char *input)
2508 {
2509   prev_lexptr = NULL;
2510   lexptr = input;
2511   paren_depth = 0;
2512 }
2513
2514 /* A test helper that lexes a string, expecting a single token.  It
2515    returns the lexer data for this token.  */
2516
2517 static RUSTSTYPE
2518 rust_lex_test_one (const char *input, int expected)
2519 {
2520   int token;
2521   RUSTSTYPE result;
2522
2523   rust_lex_test_init (input);
2524
2525   token = rustyylex ();
2526   SELF_CHECK (token == expected);
2527   result = rustyylval;
2528
2529   if (token)
2530     {
2531       token = rustyylex ();
2532       SELF_CHECK (token == 0);
2533     }
2534
2535   return result;
2536 }
2537
2538 /* Test that INPUT lexes as the integer VALUE.  */
2539
2540 static void
2541 rust_lex_int_test (const char *input, int value, int kind)
2542 {
2543   RUSTSTYPE result = rust_lex_test_one (input, kind);
2544   SELF_CHECK (result.typed_val_int.val == value);
2545 }
2546
2547 /* Test that INPUT throws an exception with text ERR.  */
2548
2549 static void
2550 rust_lex_exception_test (const char *input, const char *err)
2551 {
2552   TRY
2553     {
2554       /* The "kind" doesn't matter.  */
2555       rust_lex_test_one (input, DECIMAL_INTEGER);
2556       SELF_CHECK (0);
2557     }
2558   CATCH (except, RETURN_MASK_ERROR)
2559     {
2560       SELF_CHECK (strcmp (except.message, err) == 0);
2561     }
2562   END_CATCH
2563 }
2564
2565 /* Test that INPUT lexes as the identifier, string, or byte-string
2566    VALUE.  KIND holds the expected token kind.  */
2567
2568 static void
2569 rust_lex_stringish_test (const char *input, const char *value, int kind)
2570 {
2571   RUSTSTYPE result = rust_lex_test_one (input, kind);
2572   SELF_CHECK (result.sval.length == strlen (value));
2573   SELF_CHECK (strncmp (result.sval.ptr, value, result.sval.length) == 0);
2574 }
2575
2576 /* Helper to test that a string parses as a given token sequence.  */
2577
2578 static void
2579 rust_lex_test_sequence (const char *input, int len, const int expected[])
2580 {
2581   int i;
2582
2583   lexptr = input;
2584   paren_depth = 0;
2585
2586   for (i = 0; i < len; ++i)
2587     {
2588       int token = rustyylex ();
2589
2590       SELF_CHECK (token == expected[i]);
2591     }
2592 }
2593
2594 /* Tests for an integer-parsing corner case.  */
2595
2596 static void
2597 rust_lex_test_trailing_dot (void)
2598 {
2599   const int expected1[] = { DECIMAL_INTEGER, '.', IDENT, '(', ')', 0 };
2600   const int expected2[] = { INTEGER, '.', IDENT, '(', ')', 0 };
2601   const int expected3[] = { FLOAT, EQEQ, '(', ')', 0 };
2602   const int expected4[] = { DECIMAL_INTEGER, DOTDOT, DECIMAL_INTEGER, 0 };
2603
2604   rust_lex_test_sequence ("23.g()", ARRAY_SIZE (expected1), expected1);
2605   rust_lex_test_sequence ("23_0.g()", ARRAY_SIZE (expected2), expected2);
2606   rust_lex_test_sequence ("23.==()", ARRAY_SIZE (expected3), expected3);
2607   rust_lex_test_sequence ("23..25", ARRAY_SIZE (expected4), expected4);
2608 }
2609
2610 /* Tests of completion.  */
2611
2612 static void
2613 rust_lex_test_completion (void)
2614 {
2615   const int expected[] = { IDENT, '.', COMPLETE, 0 };
2616
2617   parse_completion = 1;
2618
2619   rust_lex_test_sequence ("something.wha", ARRAY_SIZE (expected), expected);
2620   rust_lex_test_sequence ("something.", ARRAY_SIZE (expected), expected);
2621
2622   parse_completion = 0;
2623 }
2624
2625 /* Test pushback.  */
2626
2627 static void
2628 rust_lex_test_push_back (void)
2629 {
2630   int token;
2631
2632   rust_lex_test_init (">>=");
2633
2634   token = rustyylex ();
2635   SELF_CHECK (token == COMPOUND_ASSIGN);
2636   SELF_CHECK (rustyylval.opcode == BINOP_RSH);
2637
2638   rust_push_back ('=');
2639
2640   token = rustyylex ();
2641   SELF_CHECK (token == '=');
2642
2643   token = rustyylex ();
2644   SELF_CHECK (token == 0);
2645 }
2646
2647 /* Unit test the lexer.  */
2648
2649 static void
2650 rust_lex_tests (void)
2651 {
2652   int i;
2653
2654   obstack_init (&work_obstack);
2655   unit_testing = 1;
2656
2657   rust_lex_test_one ("", 0);
2658   rust_lex_test_one ("    \t  \n \r  ", 0);
2659   rust_lex_test_one ("thread 23", 0);
2660   rust_lex_test_one ("task 23", 0);
2661   rust_lex_test_one ("th 104", 0);
2662   rust_lex_test_one ("ta 97", 0);
2663
2664   rust_lex_int_test ("'z'", 'z', INTEGER);
2665   rust_lex_int_test ("'\\xff'", 0xff, INTEGER);
2666   rust_lex_int_test ("'\\u{1016f}'", 0x1016f, INTEGER);
2667   rust_lex_int_test ("b'z'", 'z', INTEGER);
2668   rust_lex_int_test ("b'\\xfe'", 0xfe, INTEGER);
2669   rust_lex_int_test ("b'\\xFE'", 0xfe, INTEGER);
2670   rust_lex_int_test ("b'\\xfE'", 0xfe, INTEGER);
2671
2672   /* Test all escapes in both modes.  */
2673   rust_lex_int_test ("'\\n'", '\n', INTEGER);
2674   rust_lex_int_test ("'\\r'", '\r', INTEGER);
2675   rust_lex_int_test ("'\\t'", '\t', INTEGER);
2676   rust_lex_int_test ("'\\\\'", '\\', INTEGER);
2677   rust_lex_int_test ("'\\0'", '\0', INTEGER);
2678   rust_lex_int_test ("'\\''", '\'', INTEGER);
2679   rust_lex_int_test ("'\\\"'", '"', INTEGER);
2680
2681   rust_lex_int_test ("b'\\n'", '\n', INTEGER);
2682   rust_lex_int_test ("b'\\r'", '\r', INTEGER);
2683   rust_lex_int_test ("b'\\t'", '\t', INTEGER);
2684   rust_lex_int_test ("b'\\\\'", '\\', INTEGER);
2685   rust_lex_int_test ("b'\\0'", '\0', INTEGER);
2686   rust_lex_int_test ("b'\\''", '\'', INTEGER);
2687   rust_lex_int_test ("b'\\\"'", '"', INTEGER);
2688
2689   rust_lex_exception_test ("'z", "Unterminated character literal");
2690   rust_lex_exception_test ("b'\\x0'", "Not enough hex digits seen");
2691   rust_lex_exception_test ("b'\\u{0}'", "Unicode escape in byte literal");
2692   rust_lex_exception_test ("'\\x0'", "Not enough hex digits seen");
2693   rust_lex_exception_test ("'\\u0'", "Missing '{' in Unicode escape");
2694   rust_lex_exception_test ("'\\u{0", "Missing '}' in Unicode escape");
2695   rust_lex_exception_test ("'\\u{0000007}", "Overlong hex escape");
2696   rust_lex_exception_test ("'\\u{}", "Not enough hex digits seen");
2697   rust_lex_exception_test ("'\\Q'", "Invalid escape \\Q in literal");
2698   rust_lex_exception_test ("b'\\Q'", "Invalid escape \\Q in literal");
2699
2700   rust_lex_int_test ("23", 23, DECIMAL_INTEGER);
2701   rust_lex_int_test ("2_344__29", 234429, INTEGER);
2702   rust_lex_int_test ("0x1f", 0x1f, INTEGER);
2703   rust_lex_int_test ("23usize", 23, INTEGER);
2704   rust_lex_int_test ("23i32", 23, INTEGER);
2705   rust_lex_int_test ("0x1_f", 0x1f, INTEGER);
2706   rust_lex_int_test ("0b1_101011__", 0x6b, INTEGER);
2707   rust_lex_int_test ("0o001177i64", 639, INTEGER);
2708
2709   rust_lex_test_trailing_dot ();
2710
2711   rust_lex_test_one ("23.", FLOAT);
2712   rust_lex_test_one ("23.99f32", FLOAT);
2713   rust_lex_test_one ("23e7", FLOAT);
2714   rust_lex_test_one ("23E-7", FLOAT);
2715   rust_lex_test_one ("23e+7", FLOAT);
2716   rust_lex_test_one ("23.99e+7f64", FLOAT);
2717   rust_lex_test_one ("23.82f32", FLOAT);
2718
2719   rust_lex_stringish_test ("hibob", "hibob", IDENT);
2720   rust_lex_stringish_test ("hibob__93", "hibob__93", IDENT);
2721   rust_lex_stringish_test ("thread", "thread", IDENT);
2722
2723   rust_lex_stringish_test ("\"string\"", "string", STRING);
2724   rust_lex_stringish_test ("\"str\\ting\"", "str\ting", STRING);
2725   rust_lex_stringish_test ("\"str\\\"ing\"", "str\"ing", STRING);
2726   rust_lex_stringish_test ("r\"str\\ing\"", "str\\ing", STRING);
2727   rust_lex_stringish_test ("r#\"str\\ting\"#", "str\\ting", STRING);
2728   rust_lex_stringish_test ("r###\"str\\\"ing\"###", "str\\\"ing", STRING);
2729
2730   rust_lex_stringish_test ("b\"string\"", "string", BYTESTRING);
2731   rust_lex_stringish_test ("b\"\x73tring\"", "string", BYTESTRING);
2732   rust_lex_stringish_test ("b\"str\\\"ing\"", "str\"ing", BYTESTRING);
2733   rust_lex_stringish_test ("br####\"\\x73tring\"####", "\\x73tring",
2734                            BYTESTRING);
2735
2736   for (i = 0; i < ARRAY_SIZE (identifier_tokens); ++i)
2737     rust_lex_test_one (identifier_tokens[i].name, identifier_tokens[i].value);
2738
2739   for (i = 0; i < ARRAY_SIZE (operator_tokens); ++i)
2740     rust_lex_test_one (operator_tokens[i].name, operator_tokens[i].value);
2741
2742   rust_lex_test_completion ();
2743   rust_lex_test_push_back ();
2744
2745   obstack_free (&work_obstack, NULL);
2746   unit_testing = 0;
2747 }
2748
2749 #endif /* GDB_SELF_TEST */
2750
2751 void
2752 _initialize_rust_exp (void)
2753 {
2754   int code = regcomp (&number_regex, number_regex_text, REG_EXTENDED);
2755   /* If the regular expression was incorrect, it was a programming
2756      error.  */
2757   gdb_assert (code == 0);
2758
2759 #if GDB_SELF_TEST
2760   register_self_test (rust_lex_tests);
2761 #endif
2762 }