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