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