xref: /dragonfly/contrib/gdb-7/gdb/go-exp.y (revision ef5ccd6c)
1*ef5ccd6cSJohn Marino /* YACC parser for Go expressions, for GDB.
2*ef5ccd6cSJohn Marino 
3*ef5ccd6cSJohn Marino    Copyright (C) 2012-2013 Free Software Foundation, Inc.
4*ef5ccd6cSJohn Marino 
5*ef5ccd6cSJohn Marino    This file is part of GDB.
6*ef5ccd6cSJohn Marino 
7*ef5ccd6cSJohn Marino    This program is free software; you can redistribute it and/or modify
8*ef5ccd6cSJohn Marino    it under the terms of the GNU General Public License as published by
9*ef5ccd6cSJohn Marino    the Free Software Foundation; either version 3 of the License, or
10*ef5ccd6cSJohn Marino    (at your option) any later version.
11*ef5ccd6cSJohn Marino 
12*ef5ccd6cSJohn Marino    This program is distributed in the hope that it will be useful,
13*ef5ccd6cSJohn Marino    but WITHOUT ANY WARRANTY; without even the implied warranty of
14*ef5ccd6cSJohn Marino    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
15*ef5ccd6cSJohn Marino    GNU General Public License for more details.
16*ef5ccd6cSJohn Marino 
17*ef5ccd6cSJohn Marino    You should have received a copy of the GNU General Public License
18*ef5ccd6cSJohn Marino    along with this program.  If not, see <http://www.gnu.org/licenses/>.  */
19*ef5ccd6cSJohn Marino 
20*ef5ccd6cSJohn Marino /* This file is derived from c-exp.y, p-exp.y.  */
21*ef5ccd6cSJohn Marino 
22*ef5ccd6cSJohn Marino /* Parse a Go expression from text in a string,
23*ef5ccd6cSJohn Marino    and return the result as a struct expression pointer.
24*ef5ccd6cSJohn Marino    That structure contains arithmetic operations in reverse polish,
25*ef5ccd6cSJohn Marino    with constants represented by operations that are followed by special data.
26*ef5ccd6cSJohn Marino    See expression.h for the details of the format.
27*ef5ccd6cSJohn Marino    What is important here is that it can be built up sequentially
28*ef5ccd6cSJohn Marino    during the process of parsing; the lower levels of the tree always
29*ef5ccd6cSJohn Marino    come first in the result.
30*ef5ccd6cSJohn Marino 
31*ef5ccd6cSJohn Marino    Note that malloc's and realloc's in this file are transformed to
32*ef5ccd6cSJohn Marino    xmalloc and xrealloc respectively by the same sed command in the
33*ef5ccd6cSJohn Marino    makefile that remaps any other malloc/realloc inserted by the parser
34*ef5ccd6cSJohn Marino    generator.  Doing this with #defines and trying to control the interaction
35*ef5ccd6cSJohn Marino    with include files (<malloc.h> and <stdlib.h> for example) just became
36*ef5ccd6cSJohn Marino    too messy, particularly when such includes can be inserted at random
37*ef5ccd6cSJohn Marino    times by the parser generator.  */
38*ef5ccd6cSJohn Marino 
39*ef5ccd6cSJohn Marino /* Known bugs or limitations:
40*ef5ccd6cSJohn Marino 
41*ef5ccd6cSJohn Marino    - Unicode
42*ef5ccd6cSJohn Marino    - &^
43*ef5ccd6cSJohn Marino    - '_' (blank identifier)
44*ef5ccd6cSJohn Marino    - automatic deref of pointers
45*ef5ccd6cSJohn Marino    - method expressions
46*ef5ccd6cSJohn Marino    - interfaces, channels, etc.
47*ef5ccd6cSJohn Marino 
48*ef5ccd6cSJohn Marino    And lots of other things.
49*ef5ccd6cSJohn Marino    I'm sure there's some cleanup to do.
50*ef5ccd6cSJohn Marino */
51*ef5ccd6cSJohn Marino 
52*ef5ccd6cSJohn Marino %{
53*ef5ccd6cSJohn Marino 
54*ef5ccd6cSJohn Marino #include "defs.h"
55*ef5ccd6cSJohn Marino #include "gdb_string.h"
56*ef5ccd6cSJohn Marino #include <ctype.h>
57*ef5ccd6cSJohn Marino #include "expression.h"
58*ef5ccd6cSJohn Marino #include "value.h"
59*ef5ccd6cSJohn Marino #include "parser-defs.h"
60*ef5ccd6cSJohn Marino #include "language.h"
61*ef5ccd6cSJohn Marino #include "c-lang.h"
62*ef5ccd6cSJohn Marino #include "go-lang.h"
63*ef5ccd6cSJohn Marino #include "bfd.h" /* Required by objfiles.h.  */
64*ef5ccd6cSJohn Marino #include "symfile.h" /* Required by objfiles.h.  */
65*ef5ccd6cSJohn Marino #include "objfiles.h" /* For have_full_symbols and have_partial_symbols */
66*ef5ccd6cSJohn Marino #include "charset.h"
67*ef5ccd6cSJohn Marino #include "block.h"
68*ef5ccd6cSJohn Marino 
69*ef5ccd6cSJohn Marino #define parse_type builtin_type (parse_gdbarch)
70*ef5ccd6cSJohn Marino 
71*ef5ccd6cSJohn Marino /* Remap normal yacc parser interface names (yyparse, yylex, yyerror, etc),
72*ef5ccd6cSJohn Marino    as well as gratuitiously global symbol names, so we can have multiple
73*ef5ccd6cSJohn Marino    yacc generated parsers in gdb.  Note that these are only the variables
74*ef5ccd6cSJohn Marino    produced by yacc.  If other parser generators (bison, byacc, etc) produce
75*ef5ccd6cSJohn Marino    additional global names that conflict at link time, then those parser
76*ef5ccd6cSJohn Marino    generators need to be fixed instead of adding those names to this list.  */
77*ef5ccd6cSJohn Marino 
78*ef5ccd6cSJohn Marino #define	yymaxdepth go_maxdepth
79*ef5ccd6cSJohn Marino #define	yyparse	go_parse_internal
80*ef5ccd6cSJohn Marino #define	yylex	go_lex
81*ef5ccd6cSJohn Marino #define	yyerror	go_error
82*ef5ccd6cSJohn Marino #define	yylval	go_lval
83*ef5ccd6cSJohn Marino #define	yychar	go_char
84*ef5ccd6cSJohn Marino #define	yydebug	go_debug
85*ef5ccd6cSJohn Marino #define	yypact	go_pact
86*ef5ccd6cSJohn Marino #define	yyr1	go_r1
87*ef5ccd6cSJohn Marino #define	yyr2	go_r2
88*ef5ccd6cSJohn Marino #define	yydef	go_def
89*ef5ccd6cSJohn Marino #define	yychk	go_chk
90*ef5ccd6cSJohn Marino #define	yypgo	go_pgo
91*ef5ccd6cSJohn Marino #define	yyact	go_act
92*ef5ccd6cSJohn Marino #define	yyexca	go_exca
93*ef5ccd6cSJohn Marino #define yyerrflag go_errflag
94*ef5ccd6cSJohn Marino #define yynerrs	go_nerrs
95*ef5ccd6cSJohn Marino #define	yyps	go_ps
96*ef5ccd6cSJohn Marino #define	yypv	go_pv
97*ef5ccd6cSJohn Marino #define	yys	go_s
98*ef5ccd6cSJohn Marino #define	yy_yys	go_yys
99*ef5ccd6cSJohn Marino #define	yystate	go_state
100*ef5ccd6cSJohn Marino #define	yytmp	go_tmp
101*ef5ccd6cSJohn Marino #define	yyv	go_v
102*ef5ccd6cSJohn Marino #define	yy_yyv	go_yyv
103*ef5ccd6cSJohn Marino #define	yyval	go_val
104*ef5ccd6cSJohn Marino #define	yylloc	go_lloc
105*ef5ccd6cSJohn Marino #define yyreds	go_reds		/* With YYDEBUG defined */
106*ef5ccd6cSJohn Marino #define yytoks	go_toks		/* With YYDEBUG defined */
107*ef5ccd6cSJohn Marino #define yyname	go_name		/* With YYDEBUG defined */
108*ef5ccd6cSJohn Marino #define yyrule	go_rule		/* With YYDEBUG defined */
109*ef5ccd6cSJohn Marino #define yylhs	go_yylhs
110*ef5ccd6cSJohn Marino #define yylen	go_yylen
111*ef5ccd6cSJohn Marino #define yydefred go_yydefred
112*ef5ccd6cSJohn Marino #define yydgoto	go_yydgoto
113*ef5ccd6cSJohn Marino #define yysindex go_yysindex
114*ef5ccd6cSJohn Marino #define yyrindex go_yyrindex
115*ef5ccd6cSJohn Marino #define yygindex go_yygindex
116*ef5ccd6cSJohn Marino #define yytable	 go_yytable
117*ef5ccd6cSJohn Marino #define yycheck	 go_yycheck
118*ef5ccd6cSJohn Marino 
119*ef5ccd6cSJohn Marino #ifndef YYDEBUG
120*ef5ccd6cSJohn Marino #define	YYDEBUG 1		/* Default to yydebug support */
121*ef5ccd6cSJohn Marino #endif
122*ef5ccd6cSJohn Marino 
123*ef5ccd6cSJohn Marino #define YYFPRINTF parser_fprintf
124*ef5ccd6cSJohn Marino 
125*ef5ccd6cSJohn Marino int yyparse (void);
126*ef5ccd6cSJohn Marino 
127*ef5ccd6cSJohn Marino static int yylex (void);
128*ef5ccd6cSJohn Marino 
129*ef5ccd6cSJohn Marino void yyerror (char *);
130*ef5ccd6cSJohn Marino 
131*ef5ccd6cSJohn Marino %}
132*ef5ccd6cSJohn Marino 
133*ef5ccd6cSJohn Marino /* Although the yacc "value" of an expression is not used,
134*ef5ccd6cSJohn Marino    since the result is stored in the structure being created,
135*ef5ccd6cSJohn Marino    other node types do have values.  */
136*ef5ccd6cSJohn Marino 
137*ef5ccd6cSJohn Marino %union
138*ef5ccd6cSJohn Marino   {
139*ef5ccd6cSJohn Marino     LONGEST lval;
140*ef5ccd6cSJohn Marino     struct {
141*ef5ccd6cSJohn Marino       LONGEST val;
142*ef5ccd6cSJohn Marino       struct type *type;
143*ef5ccd6cSJohn Marino     } typed_val_int;
144*ef5ccd6cSJohn Marino     struct {
145*ef5ccd6cSJohn Marino       DOUBLEST dval;
146*ef5ccd6cSJohn Marino       struct type *type;
147*ef5ccd6cSJohn Marino     } typed_val_float;
148*ef5ccd6cSJohn Marino     struct stoken sval;
149*ef5ccd6cSJohn Marino     struct symtoken ssym;
150*ef5ccd6cSJohn Marino     struct type *tval;
151*ef5ccd6cSJohn Marino     struct typed_stoken tsval;
152*ef5ccd6cSJohn Marino     struct ttype tsym;
153*ef5ccd6cSJohn Marino     int voidval;
154*ef5ccd6cSJohn Marino     enum exp_opcode opcode;
155*ef5ccd6cSJohn Marino     struct internalvar *ivar;
156*ef5ccd6cSJohn Marino     struct stoken_vector svec;
157*ef5ccd6cSJohn Marino   }
158*ef5ccd6cSJohn Marino 
159*ef5ccd6cSJohn Marino %{
160*ef5ccd6cSJohn Marino /* YYSTYPE gets defined by %union.  */
161*ef5ccd6cSJohn Marino static int parse_number (char *, int, int, YYSTYPE *);
162*ef5ccd6cSJohn Marino static int parse_go_float (struct gdbarch *gdbarch, const char *p, int len,
163*ef5ccd6cSJohn Marino 			   DOUBLEST *d, struct type **t);
164*ef5ccd6cSJohn Marino %}
165*ef5ccd6cSJohn Marino 
166*ef5ccd6cSJohn Marino %type <voidval> exp exp1 type_exp start variable lcurly
167*ef5ccd6cSJohn Marino %type <lval> rcurly
168*ef5ccd6cSJohn Marino %type <tval> type
169*ef5ccd6cSJohn Marino 
170*ef5ccd6cSJohn Marino %token <typed_val_int> INT
171*ef5ccd6cSJohn Marino %token <typed_val_float> FLOAT
172*ef5ccd6cSJohn Marino 
173*ef5ccd6cSJohn Marino /* Both NAME and TYPENAME tokens represent symbols in the input,
174*ef5ccd6cSJohn Marino    and both convey their data as strings.
175*ef5ccd6cSJohn Marino    But a TYPENAME is a string that happens to be defined as a type
176*ef5ccd6cSJohn Marino    or builtin type name (such as int or char)
177*ef5ccd6cSJohn Marino    and a NAME is any other symbol.
178*ef5ccd6cSJohn Marino    Contexts where this distinction is not important can use the
179*ef5ccd6cSJohn Marino    nonterminal "name", which matches either NAME or TYPENAME.  */
180*ef5ccd6cSJohn Marino 
181*ef5ccd6cSJohn Marino %token <tsval> RAW_STRING
182*ef5ccd6cSJohn Marino %token <tsval> STRING
183*ef5ccd6cSJohn Marino %token <tsval> CHAR
184*ef5ccd6cSJohn Marino %token <ssym> NAME
185*ef5ccd6cSJohn Marino %token <tsym> TYPENAME /* Not TYPE_NAME cus already taken.  */
186*ef5ccd6cSJohn Marino %token <voidval> COMPLETE
187*ef5ccd6cSJohn Marino /*%type <sval> name*/
188*ef5ccd6cSJohn Marino %type <svec> string_exp
189*ef5ccd6cSJohn Marino %type <ssym> name_not_typename
190*ef5ccd6cSJohn Marino 
191*ef5ccd6cSJohn Marino /* A NAME_OR_INT is a symbol which is not known in the symbol table,
192*ef5ccd6cSJohn Marino    but which would parse as a valid number in the current input radix.
193*ef5ccd6cSJohn Marino    E.g. "c" when input_radix==16.  Depending on the parse, it will be
194*ef5ccd6cSJohn Marino    turned into a name or into a number.  */
195*ef5ccd6cSJohn Marino %token <ssym> NAME_OR_INT
196*ef5ccd6cSJohn Marino 
197*ef5ccd6cSJohn Marino %token <lval> TRUE_KEYWORD FALSE_KEYWORD
198*ef5ccd6cSJohn Marino %token STRUCT_KEYWORD INTERFACE_KEYWORD TYPE_KEYWORD CHAN_KEYWORD
199*ef5ccd6cSJohn Marino %token SIZEOF_KEYWORD
200*ef5ccd6cSJohn Marino %token LEN_KEYWORD CAP_KEYWORD
201*ef5ccd6cSJohn Marino %token NEW_KEYWORD
202*ef5ccd6cSJohn Marino %token IOTA_KEYWORD NIL_KEYWORD
203*ef5ccd6cSJohn Marino %token CONST_KEYWORD
204*ef5ccd6cSJohn Marino %token DOTDOTDOT
205*ef5ccd6cSJohn Marino %token ENTRY
206*ef5ccd6cSJohn Marino %token ERROR
207*ef5ccd6cSJohn Marino 
208*ef5ccd6cSJohn Marino /* Special type cases.  */
209*ef5ccd6cSJohn Marino %token BYTE_KEYWORD /* An alias of uint8.  */
210*ef5ccd6cSJohn Marino 
211*ef5ccd6cSJohn Marino %token <sval> DOLLAR_VARIABLE
212*ef5ccd6cSJohn Marino 
213*ef5ccd6cSJohn Marino %token <opcode> ASSIGN_MODIFY
214*ef5ccd6cSJohn Marino 
215*ef5ccd6cSJohn Marino %left ','
216*ef5ccd6cSJohn Marino %left ABOVE_COMMA
217*ef5ccd6cSJohn Marino %right '=' ASSIGN_MODIFY
218*ef5ccd6cSJohn Marino %right '?'
219*ef5ccd6cSJohn Marino %left OROR
220*ef5ccd6cSJohn Marino %left ANDAND
221*ef5ccd6cSJohn Marino %left '|'
222*ef5ccd6cSJohn Marino %left '^'
223*ef5ccd6cSJohn Marino %left '&'
224*ef5ccd6cSJohn Marino %left ANDNOT
225*ef5ccd6cSJohn Marino %left EQUAL NOTEQUAL
226*ef5ccd6cSJohn Marino %left '<' '>' LEQ GEQ
227*ef5ccd6cSJohn Marino %left LSH RSH
228*ef5ccd6cSJohn Marino %left '@'
229*ef5ccd6cSJohn Marino %left '+' '-'
230*ef5ccd6cSJohn Marino %left '*' '/' '%'
231*ef5ccd6cSJohn Marino %right UNARY INCREMENT DECREMENT
232*ef5ccd6cSJohn Marino %right LEFT_ARROW '.' '[' '('
233*ef5ccd6cSJohn Marino 
234*ef5ccd6cSJohn Marino 
235*ef5ccd6cSJohn Marino %%
236*ef5ccd6cSJohn Marino 
237*ef5ccd6cSJohn Marino start   :	exp1
238*ef5ccd6cSJohn Marino 	|	type_exp
239*ef5ccd6cSJohn Marino 	;
240*ef5ccd6cSJohn Marino 
241*ef5ccd6cSJohn Marino type_exp:	type
242*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode(OP_TYPE);
243*ef5ccd6cSJohn Marino 			  write_exp_elt_type($1);
244*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode(OP_TYPE); }
245*ef5ccd6cSJohn Marino 	;
246*ef5ccd6cSJohn Marino 
247*ef5ccd6cSJohn Marino /* Expressions, including the comma operator.  */
248*ef5ccd6cSJohn Marino exp1	:	exp
249*ef5ccd6cSJohn Marino 	|	exp1 ',' exp
250*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_COMMA); }
251*ef5ccd6cSJohn Marino 	;
252*ef5ccd6cSJohn Marino 
253*ef5ccd6cSJohn Marino /* Expressions, not including the comma operator.  */
254*ef5ccd6cSJohn Marino exp	:	'*' exp    %prec UNARY
255*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_IND); }
256*ef5ccd6cSJohn Marino 	;
257*ef5ccd6cSJohn Marino 
258*ef5ccd6cSJohn Marino exp	:	'&' exp    %prec UNARY
259*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_ADDR); }
260*ef5ccd6cSJohn Marino 	;
261*ef5ccd6cSJohn Marino 
262*ef5ccd6cSJohn Marino exp	:	'-' exp    %prec UNARY
263*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_NEG); }
264*ef5ccd6cSJohn Marino 	;
265*ef5ccd6cSJohn Marino 
266*ef5ccd6cSJohn Marino exp	:	'+' exp    %prec UNARY
267*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_PLUS); }
268*ef5ccd6cSJohn Marino 	;
269*ef5ccd6cSJohn Marino 
270*ef5ccd6cSJohn Marino exp	:	'!' exp    %prec UNARY
271*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_LOGICAL_NOT); }
272*ef5ccd6cSJohn Marino 	;
273*ef5ccd6cSJohn Marino 
274*ef5ccd6cSJohn Marino exp	:	'^' exp    %prec UNARY
275*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_COMPLEMENT); }
276*ef5ccd6cSJohn Marino 	;
277*ef5ccd6cSJohn Marino 
278*ef5ccd6cSJohn Marino exp	:	exp INCREMENT    %prec UNARY
279*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_POSTINCREMENT); }
280*ef5ccd6cSJohn Marino 	;
281*ef5ccd6cSJohn Marino 
282*ef5ccd6cSJohn Marino exp	:	exp DECREMENT    %prec UNARY
283*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_POSTDECREMENT); }
284*ef5ccd6cSJohn Marino 	;
285*ef5ccd6cSJohn Marino 
286*ef5ccd6cSJohn Marino /* foo->bar is not in Go.  May want as a gdb extension.  Later.  */
287*ef5ccd6cSJohn Marino 
288*ef5ccd6cSJohn Marino exp	:	exp '.' name_not_typename
289*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (STRUCTOP_STRUCT);
290*ef5ccd6cSJohn Marino 			  write_exp_string ($3.stoken);
291*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (STRUCTOP_STRUCT); }
292*ef5ccd6cSJohn Marino 	;
293*ef5ccd6cSJohn Marino 
294*ef5ccd6cSJohn Marino exp	:	exp '.' name_not_typename COMPLETE
295*ef5ccd6cSJohn Marino 			{ mark_struct_expression ();
296*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (STRUCTOP_STRUCT);
297*ef5ccd6cSJohn Marino 			  write_exp_string ($3.stoken);
298*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (STRUCTOP_STRUCT); }
299*ef5ccd6cSJohn Marino 	;
300*ef5ccd6cSJohn Marino 
301*ef5ccd6cSJohn Marino exp	:	exp '.' COMPLETE
302*ef5ccd6cSJohn Marino 			{ struct stoken s;
303*ef5ccd6cSJohn Marino 			  mark_struct_expression ();
304*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (STRUCTOP_STRUCT);
305*ef5ccd6cSJohn Marino 			  s.ptr = "";
306*ef5ccd6cSJohn Marino 			  s.length = 0;
307*ef5ccd6cSJohn Marino 			  write_exp_string (s);
308*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (STRUCTOP_STRUCT); }
309*ef5ccd6cSJohn Marino 	;
310*ef5ccd6cSJohn Marino 
311*ef5ccd6cSJohn Marino exp	:	exp '[' exp1 ']'
312*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_SUBSCRIPT); }
313*ef5ccd6cSJohn Marino 	;
314*ef5ccd6cSJohn Marino 
315*ef5ccd6cSJohn Marino exp	:	exp '('
316*ef5ccd6cSJohn Marino 			/* This is to save the value of arglist_len
317*ef5ccd6cSJohn Marino 			   being accumulated by an outer function call.  */
318*ef5ccd6cSJohn Marino 			{ start_arglist (); }
319*ef5ccd6cSJohn Marino 		arglist ')'	%prec LEFT_ARROW
320*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (OP_FUNCALL);
321*ef5ccd6cSJohn Marino 			  write_exp_elt_longcst ((LONGEST) end_arglist ());
322*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_FUNCALL); }
323*ef5ccd6cSJohn Marino 	;
324*ef5ccd6cSJohn Marino 
325*ef5ccd6cSJohn Marino lcurly	:	'{'
326*ef5ccd6cSJohn Marino 			{ start_arglist (); }
327*ef5ccd6cSJohn Marino 	;
328*ef5ccd6cSJohn Marino 
329*ef5ccd6cSJohn Marino arglist	:
330*ef5ccd6cSJohn Marino 	;
331*ef5ccd6cSJohn Marino 
332*ef5ccd6cSJohn Marino arglist	:	exp
333*ef5ccd6cSJohn Marino 			{ arglist_len = 1; }
334*ef5ccd6cSJohn Marino 	;
335*ef5ccd6cSJohn Marino 
336*ef5ccd6cSJohn Marino arglist	:	arglist ',' exp   %prec ABOVE_COMMA
337*ef5ccd6cSJohn Marino 			{ arglist_len++; }
338*ef5ccd6cSJohn Marino 	;
339*ef5ccd6cSJohn Marino 
340*ef5ccd6cSJohn Marino rcurly	:	'}'
341*ef5ccd6cSJohn Marino 			{ $$ = end_arglist () - 1; }
342*ef5ccd6cSJohn Marino 	;
343*ef5ccd6cSJohn Marino 
344*ef5ccd6cSJohn Marino exp	:	lcurly type rcurly exp  %prec UNARY
345*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_MEMVAL);
346*ef5ccd6cSJohn Marino 			  write_exp_elt_type ($2);
347*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (UNOP_MEMVAL); }
348*ef5ccd6cSJohn Marino 	;
349*ef5ccd6cSJohn Marino 
350*ef5ccd6cSJohn Marino exp	:	type '(' exp ')'  %prec UNARY
351*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (UNOP_CAST);
352*ef5ccd6cSJohn Marino 			  write_exp_elt_type ($1);
353*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (UNOP_CAST); }
354*ef5ccd6cSJohn Marino 	;
355*ef5ccd6cSJohn Marino 
356*ef5ccd6cSJohn Marino exp	:	'(' exp1 ')'
357*ef5ccd6cSJohn Marino 			{ }
358*ef5ccd6cSJohn Marino 	;
359*ef5ccd6cSJohn Marino 
360*ef5ccd6cSJohn Marino /* Binary operators in order of decreasing precedence.  */
361*ef5ccd6cSJohn Marino 
362*ef5ccd6cSJohn Marino exp	:	exp '@' exp
363*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_REPEAT); }
364*ef5ccd6cSJohn Marino 	;
365*ef5ccd6cSJohn Marino 
366*ef5ccd6cSJohn Marino exp	:	exp '*' exp
367*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_MUL); }
368*ef5ccd6cSJohn Marino 	;
369*ef5ccd6cSJohn Marino 
370*ef5ccd6cSJohn Marino exp	:	exp '/' exp
371*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_DIV); }
372*ef5ccd6cSJohn Marino 	;
373*ef5ccd6cSJohn Marino 
374*ef5ccd6cSJohn Marino exp	:	exp '%' exp
375*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_REM); }
376*ef5ccd6cSJohn Marino 	;
377*ef5ccd6cSJohn Marino 
378*ef5ccd6cSJohn Marino exp	:	exp '+' exp
379*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_ADD); }
380*ef5ccd6cSJohn Marino 	;
381*ef5ccd6cSJohn Marino 
382*ef5ccd6cSJohn Marino exp	:	exp '-' exp
383*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_SUB); }
384*ef5ccd6cSJohn Marino 	;
385*ef5ccd6cSJohn Marino 
386*ef5ccd6cSJohn Marino exp	:	exp LSH exp
387*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_LSH); }
388*ef5ccd6cSJohn Marino 	;
389*ef5ccd6cSJohn Marino 
390*ef5ccd6cSJohn Marino exp	:	exp RSH exp
391*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_RSH); }
392*ef5ccd6cSJohn Marino 	;
393*ef5ccd6cSJohn Marino 
394*ef5ccd6cSJohn Marino exp	:	exp EQUAL exp
395*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_EQUAL); }
396*ef5ccd6cSJohn Marino 	;
397*ef5ccd6cSJohn Marino 
398*ef5ccd6cSJohn Marino exp	:	exp NOTEQUAL exp
399*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_NOTEQUAL); }
400*ef5ccd6cSJohn Marino 	;
401*ef5ccd6cSJohn Marino 
402*ef5ccd6cSJohn Marino exp	:	exp LEQ exp
403*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_LEQ); }
404*ef5ccd6cSJohn Marino 	;
405*ef5ccd6cSJohn Marino 
406*ef5ccd6cSJohn Marino exp	:	exp GEQ exp
407*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_GEQ); }
408*ef5ccd6cSJohn Marino 	;
409*ef5ccd6cSJohn Marino 
410*ef5ccd6cSJohn Marino exp	:	exp '<' exp
411*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_LESS); }
412*ef5ccd6cSJohn Marino 	;
413*ef5ccd6cSJohn Marino 
414*ef5ccd6cSJohn Marino exp	:	exp '>' exp
415*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_GTR); }
416*ef5ccd6cSJohn Marino 	;
417*ef5ccd6cSJohn Marino 
418*ef5ccd6cSJohn Marino exp	:	exp '&' exp
419*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_BITWISE_AND); }
420*ef5ccd6cSJohn Marino 	;
421*ef5ccd6cSJohn Marino 
422*ef5ccd6cSJohn Marino exp	:	exp '^' exp
423*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_BITWISE_XOR); }
424*ef5ccd6cSJohn Marino 	;
425*ef5ccd6cSJohn Marino 
426*ef5ccd6cSJohn Marino exp	:	exp '|' exp
427*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_BITWISE_IOR); }
428*ef5ccd6cSJohn Marino 	;
429*ef5ccd6cSJohn Marino 
430*ef5ccd6cSJohn Marino exp	:	exp ANDAND exp
431*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_LOGICAL_AND); }
432*ef5ccd6cSJohn Marino 	;
433*ef5ccd6cSJohn Marino 
434*ef5ccd6cSJohn Marino exp	:	exp OROR exp
435*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_LOGICAL_OR); }
436*ef5ccd6cSJohn Marino 	;
437*ef5ccd6cSJohn Marino 
438*ef5ccd6cSJohn Marino exp	:	exp '?' exp ':' exp	%prec '?'
439*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (TERNOP_COND); }
440*ef5ccd6cSJohn Marino 	;
441*ef5ccd6cSJohn Marino 
442*ef5ccd6cSJohn Marino exp	:	exp '=' exp
443*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_ASSIGN); }
444*ef5ccd6cSJohn Marino 	;
445*ef5ccd6cSJohn Marino 
446*ef5ccd6cSJohn Marino exp	:	exp ASSIGN_MODIFY exp
447*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
448*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode ($2);
449*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
450*ef5ccd6cSJohn Marino 	;
451*ef5ccd6cSJohn Marino 
452*ef5ccd6cSJohn Marino exp	:	INT
453*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (OP_LONG);
454*ef5ccd6cSJohn Marino 			  write_exp_elt_type ($1.type);
455*ef5ccd6cSJohn Marino 			  write_exp_elt_longcst ((LONGEST)($1.val));
456*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_LONG); }
457*ef5ccd6cSJohn Marino 	;
458*ef5ccd6cSJohn Marino 
459*ef5ccd6cSJohn Marino exp	:	CHAR
460*ef5ccd6cSJohn Marino 			{
461*ef5ccd6cSJohn Marino 			  struct stoken_vector vec;
462*ef5ccd6cSJohn Marino 			  vec.len = 1;
463*ef5ccd6cSJohn Marino 			  vec.tokens = &$1;
464*ef5ccd6cSJohn Marino 			  write_exp_string_vector ($1.type, &vec);
465*ef5ccd6cSJohn Marino 			}
466*ef5ccd6cSJohn Marino 	;
467*ef5ccd6cSJohn Marino 
468*ef5ccd6cSJohn Marino exp	:	NAME_OR_INT
469*ef5ccd6cSJohn Marino 			{ YYSTYPE val;
470*ef5ccd6cSJohn Marino 			  parse_number ($1.stoken.ptr, $1.stoken.length,
471*ef5ccd6cSJohn Marino 					0, &val);
472*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_LONG);
473*ef5ccd6cSJohn Marino 			  write_exp_elt_type (val.typed_val_int.type);
474*ef5ccd6cSJohn Marino 			  write_exp_elt_longcst ((LONGEST)
475*ef5ccd6cSJohn Marino 						 val.typed_val_int.val);
476*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_LONG);
477*ef5ccd6cSJohn Marino 			}
478*ef5ccd6cSJohn Marino 	;
479*ef5ccd6cSJohn Marino 
480*ef5ccd6cSJohn Marino 
481*ef5ccd6cSJohn Marino exp	:	FLOAT
482*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (OP_DOUBLE);
483*ef5ccd6cSJohn Marino 			  write_exp_elt_type ($1.type);
484*ef5ccd6cSJohn Marino 			  write_exp_elt_dblcst ($1.dval);
485*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_DOUBLE); }
486*ef5ccd6cSJohn Marino 	;
487*ef5ccd6cSJohn Marino 
488*ef5ccd6cSJohn Marino exp	:	variable
489*ef5ccd6cSJohn Marino 	;
490*ef5ccd6cSJohn Marino 
491*ef5ccd6cSJohn Marino exp	:	DOLLAR_VARIABLE
492*ef5ccd6cSJohn Marino 			{
493*ef5ccd6cSJohn Marino 			  write_dollar_variable ($1);
494*ef5ccd6cSJohn Marino 			}
495*ef5ccd6cSJohn Marino 	;
496*ef5ccd6cSJohn Marino 
497*ef5ccd6cSJohn Marino exp	:	SIZEOF_KEYWORD '(' type ')'  %prec UNARY
498*ef5ccd6cSJohn Marino 			{
499*ef5ccd6cSJohn Marino 			  /* TODO(dje): Go objects in structs.  */
500*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_LONG);
501*ef5ccd6cSJohn Marino 			  /* TODO(dje): What's the right type here?  */
502*ef5ccd6cSJohn Marino 			  write_exp_elt_type (parse_type->builtin_unsigned_int);
503*ef5ccd6cSJohn Marino 			  CHECK_TYPEDEF ($3);
504*ef5ccd6cSJohn Marino 			  write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
505*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_LONG);
506*ef5ccd6cSJohn Marino 			}
507*ef5ccd6cSJohn Marino 	;
508*ef5ccd6cSJohn Marino 
509*ef5ccd6cSJohn Marino exp	:	SIZEOF_KEYWORD  '(' exp ')'  %prec UNARY
510*ef5ccd6cSJohn Marino 			{
511*ef5ccd6cSJohn Marino 			  /* TODO(dje): Go objects in structs.  */
512*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (UNOP_SIZEOF);
513*ef5ccd6cSJohn Marino 			}
514*ef5ccd6cSJohn Marino 
515*ef5ccd6cSJohn Marino string_exp:
516*ef5ccd6cSJohn Marino 		STRING
517*ef5ccd6cSJohn Marino 			{
518*ef5ccd6cSJohn Marino 			  /* We copy the string here, and not in the
519*ef5ccd6cSJohn Marino 			     lexer, to guarantee that we do not leak a
520*ef5ccd6cSJohn Marino 			     string.  */
521*ef5ccd6cSJohn Marino 			  /* Note that we NUL-terminate here, but just
522*ef5ccd6cSJohn Marino 			     for convenience.  */
523*ef5ccd6cSJohn Marino 			  struct typed_stoken *vec = XNEW (struct typed_stoken);
524*ef5ccd6cSJohn Marino 			  $$.len = 1;
525*ef5ccd6cSJohn Marino 			  $$.tokens = vec;
526*ef5ccd6cSJohn Marino 
527*ef5ccd6cSJohn Marino 			  vec->type = $1.type;
528*ef5ccd6cSJohn Marino 			  vec->length = $1.length;
529*ef5ccd6cSJohn Marino 			  vec->ptr = malloc ($1.length + 1);
530*ef5ccd6cSJohn Marino 			  memcpy (vec->ptr, $1.ptr, $1.length + 1);
531*ef5ccd6cSJohn Marino 			}
532*ef5ccd6cSJohn Marino 
533*ef5ccd6cSJohn Marino 	|	string_exp '+' STRING
534*ef5ccd6cSJohn Marino 			{
535*ef5ccd6cSJohn Marino 			  /* Note that we NUL-terminate here, but just
536*ef5ccd6cSJohn Marino 			     for convenience.  */
537*ef5ccd6cSJohn Marino 			  char *p;
538*ef5ccd6cSJohn Marino 			  ++$$.len;
539*ef5ccd6cSJohn Marino 			  $$.tokens = realloc ($$.tokens,
540*ef5ccd6cSJohn Marino 					       $$.len * sizeof (struct typed_stoken));
541*ef5ccd6cSJohn Marino 
542*ef5ccd6cSJohn Marino 			  p = malloc ($3.length + 1);
543*ef5ccd6cSJohn Marino 			  memcpy (p, $3.ptr, $3.length + 1);
544*ef5ccd6cSJohn Marino 
545*ef5ccd6cSJohn Marino 			  $$.tokens[$$.len - 1].type = $3.type;
546*ef5ccd6cSJohn Marino 			  $$.tokens[$$.len - 1].length = $3.length;
547*ef5ccd6cSJohn Marino 			  $$.tokens[$$.len - 1].ptr = p;
548*ef5ccd6cSJohn Marino 			}
549*ef5ccd6cSJohn Marino 	;
550*ef5ccd6cSJohn Marino 
551*ef5ccd6cSJohn Marino exp	:	string_exp  %prec ABOVE_COMMA
552*ef5ccd6cSJohn Marino 			{
553*ef5ccd6cSJohn Marino 			  int i;
554*ef5ccd6cSJohn Marino 
555*ef5ccd6cSJohn Marino 			  write_exp_string_vector (0 /*always utf8*/, &$1);
556*ef5ccd6cSJohn Marino 			  for (i = 0; i < $1.len; ++i)
557*ef5ccd6cSJohn Marino 			    free ($1.tokens[i].ptr);
558*ef5ccd6cSJohn Marino 			  free ($1.tokens);
559*ef5ccd6cSJohn Marino 			}
560*ef5ccd6cSJohn Marino 	;
561*ef5ccd6cSJohn Marino 
562*ef5ccd6cSJohn Marino exp	:	TRUE_KEYWORD
563*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (OP_BOOL);
564*ef5ccd6cSJohn Marino 			  write_exp_elt_longcst ((LONGEST) $1);
565*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_BOOL); }
566*ef5ccd6cSJohn Marino 	;
567*ef5ccd6cSJohn Marino 
568*ef5ccd6cSJohn Marino exp	:	FALSE_KEYWORD
569*ef5ccd6cSJohn Marino 			{ write_exp_elt_opcode (OP_BOOL);
570*ef5ccd6cSJohn Marino 			  write_exp_elt_longcst ((LONGEST) $1);
571*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_BOOL); }
572*ef5ccd6cSJohn Marino 	;
573*ef5ccd6cSJohn Marino 
574*ef5ccd6cSJohn Marino variable:	name_not_typename ENTRY
575*ef5ccd6cSJohn Marino 			{ struct symbol *sym = $1.sym;
576*ef5ccd6cSJohn Marino 
577*ef5ccd6cSJohn Marino 			  if (sym == NULL
578*ef5ccd6cSJohn Marino 			      || !SYMBOL_IS_ARGUMENT (sym)
579*ef5ccd6cSJohn Marino 			      || !symbol_read_needs_frame (sym))
580*ef5ccd6cSJohn Marino 			    error (_("@entry can be used only for function "
581*ef5ccd6cSJohn Marino 				     "parameters, not for \"%s\""),
582*ef5ccd6cSJohn Marino 				   copy_name ($1.stoken));
583*ef5ccd6cSJohn Marino 
584*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_VAR_ENTRY_VALUE);
585*ef5ccd6cSJohn Marino 			  write_exp_elt_sym (sym);
586*ef5ccd6cSJohn Marino 			  write_exp_elt_opcode (OP_VAR_ENTRY_VALUE);
587*ef5ccd6cSJohn Marino 			}
588*ef5ccd6cSJohn Marino 	;
589*ef5ccd6cSJohn Marino 
590*ef5ccd6cSJohn Marino variable:	name_not_typename
591*ef5ccd6cSJohn Marino 			{ struct symbol *sym = $1.sym;
592*ef5ccd6cSJohn Marino 
593*ef5ccd6cSJohn Marino 			  if (sym)
594*ef5ccd6cSJohn Marino 			    {
595*ef5ccd6cSJohn Marino 			      if (symbol_read_needs_frame (sym))
596*ef5ccd6cSJohn Marino 				{
597*ef5ccd6cSJohn Marino 				  if (innermost_block == 0
598*ef5ccd6cSJohn Marino 				      || contained_in (block_found,
599*ef5ccd6cSJohn Marino 						       innermost_block))
600*ef5ccd6cSJohn Marino 				    innermost_block = block_found;
601*ef5ccd6cSJohn Marino 				}
602*ef5ccd6cSJohn Marino 
603*ef5ccd6cSJohn Marino 			      write_exp_elt_opcode (OP_VAR_VALUE);
604*ef5ccd6cSJohn Marino 			      /* We want to use the selected frame, not
605*ef5ccd6cSJohn Marino 				 another more inner frame which happens to
606*ef5ccd6cSJohn Marino 				 be in the same block.  */
607*ef5ccd6cSJohn Marino 			      write_exp_elt_block (NULL);
608*ef5ccd6cSJohn Marino 			      write_exp_elt_sym (sym);
609*ef5ccd6cSJohn Marino 			      write_exp_elt_opcode (OP_VAR_VALUE);
610*ef5ccd6cSJohn Marino 			    }
611*ef5ccd6cSJohn Marino 			  else if ($1.is_a_field_of_this)
612*ef5ccd6cSJohn Marino 			    {
613*ef5ccd6cSJohn Marino 			      /* TODO(dje): Can we get here?
614*ef5ccd6cSJohn Marino 				 E.g., via a mix of c++ and go?  */
615*ef5ccd6cSJohn Marino 			      gdb_assert_not_reached ("go with `this' field");
616*ef5ccd6cSJohn Marino 			    }
617*ef5ccd6cSJohn Marino 			  else
618*ef5ccd6cSJohn Marino 			    {
619*ef5ccd6cSJohn Marino 			      struct minimal_symbol *msymbol;
620*ef5ccd6cSJohn Marino 			      char *arg = copy_name ($1.stoken);
621*ef5ccd6cSJohn Marino 
622*ef5ccd6cSJohn Marino 			      msymbol =
623*ef5ccd6cSJohn Marino 				lookup_minimal_symbol (arg, NULL, NULL);
624*ef5ccd6cSJohn Marino 			      if (msymbol != NULL)
625*ef5ccd6cSJohn Marino 				write_exp_msymbol (msymbol);
626*ef5ccd6cSJohn Marino 			      else if (!have_full_symbols ()
627*ef5ccd6cSJohn Marino 				       && !have_partial_symbols ())
628*ef5ccd6cSJohn Marino 				error (_("No symbol table is loaded.  "
629*ef5ccd6cSJohn Marino 				       "Use the \"file\" command."));
630*ef5ccd6cSJohn Marino 			      else
631*ef5ccd6cSJohn Marino 				error (_("No symbol \"%s\" in current context."),
632*ef5ccd6cSJohn Marino 				       copy_name ($1.stoken));
633*ef5ccd6cSJohn Marino 			    }
634*ef5ccd6cSJohn Marino 			}
635*ef5ccd6cSJohn Marino 	;
636*ef5ccd6cSJohn Marino 
637*ef5ccd6cSJohn Marino /* TODO
638*ef5ccd6cSJohn Marino method_exp: PACKAGENAME '.' name '.' name
639*ef5ccd6cSJohn Marino 			{
640*ef5ccd6cSJohn Marino 			}
641*ef5ccd6cSJohn Marino 	;
642*ef5ccd6cSJohn Marino */
643*ef5ccd6cSJohn Marino 
644*ef5ccd6cSJohn Marino type  /* Implements (approximately): [*] type-specifier */
645*ef5ccd6cSJohn Marino 	:	'*' type
646*ef5ccd6cSJohn Marino 			{ $$ = lookup_pointer_type ($2); }
647*ef5ccd6cSJohn Marino 	|	TYPENAME
648*ef5ccd6cSJohn Marino 			{ $$ = $1.type; }
649*ef5ccd6cSJohn Marino /*
650*ef5ccd6cSJohn Marino 	|	STRUCT_KEYWORD name
651*ef5ccd6cSJohn Marino 			{ $$ = lookup_struct (copy_name ($2),
652*ef5ccd6cSJohn Marino 					      expression_context_block); }
653*ef5ccd6cSJohn Marino */
654*ef5ccd6cSJohn Marino 	|	BYTE_KEYWORD
655*ef5ccd6cSJohn Marino 			{ $$ = builtin_go_type (parse_gdbarch)
656*ef5ccd6cSJohn Marino 			    ->builtin_uint8; }
657*ef5ccd6cSJohn Marino 	;
658*ef5ccd6cSJohn Marino 
659*ef5ccd6cSJohn Marino /* TODO
660*ef5ccd6cSJohn Marino name	:	NAME { $$ = $1.stoken; }
661*ef5ccd6cSJohn Marino 	|	TYPENAME { $$ = $1.stoken; }
662*ef5ccd6cSJohn Marino 	|	NAME_OR_INT  { $$ = $1.stoken; }
663*ef5ccd6cSJohn Marino 	;
664*ef5ccd6cSJohn Marino */
665*ef5ccd6cSJohn Marino 
666*ef5ccd6cSJohn Marino name_not_typename
667*ef5ccd6cSJohn Marino 	:	NAME
668*ef5ccd6cSJohn Marino /* These would be useful if name_not_typename was useful, but it is just
669*ef5ccd6cSJohn Marino    a fake for "variable", so these cause reduce/reduce conflicts because
670*ef5ccd6cSJohn Marino    the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
671*ef5ccd6cSJohn Marino    =exp) or just an exp.  If name_not_typename was ever used in an lvalue
672*ef5ccd6cSJohn Marino    context where only a name could occur, this might be useful.
673*ef5ccd6cSJohn Marino 	|	NAME_OR_INT
674*ef5ccd6cSJohn Marino */
675*ef5ccd6cSJohn Marino 	;
676*ef5ccd6cSJohn Marino 
677*ef5ccd6cSJohn Marino %%
678*ef5ccd6cSJohn Marino 
679*ef5ccd6cSJohn Marino /* Wrapper on parse_c_float to get the type right for Go.  */
680*ef5ccd6cSJohn Marino 
681*ef5ccd6cSJohn Marino static int
682*ef5ccd6cSJohn Marino parse_go_float (struct gdbarch *gdbarch, const char *p, int len,
683*ef5ccd6cSJohn Marino 		DOUBLEST *d, struct type **t)
684*ef5ccd6cSJohn Marino {
685*ef5ccd6cSJohn Marino   int result = parse_c_float (gdbarch, p, len, d, t);
686*ef5ccd6cSJohn Marino   const struct builtin_type *builtin_types = builtin_type (gdbarch);
687*ef5ccd6cSJohn Marino   const struct builtin_go_type *builtin_go_types = builtin_go_type (gdbarch);
688*ef5ccd6cSJohn Marino 
689*ef5ccd6cSJohn Marino   if (*t == builtin_types->builtin_float)
690*ef5ccd6cSJohn Marino     *t = builtin_go_types->builtin_float32;
691*ef5ccd6cSJohn Marino   else if (*t == builtin_types->builtin_double)
692*ef5ccd6cSJohn Marino     *t = builtin_go_types->builtin_float64;
693*ef5ccd6cSJohn Marino 
694*ef5ccd6cSJohn Marino   return result;
695*ef5ccd6cSJohn Marino }
696*ef5ccd6cSJohn Marino 
697*ef5ccd6cSJohn Marino /* Take care of parsing a number (anything that starts with a digit).
698*ef5ccd6cSJohn Marino    Set yylval and return the token type; update lexptr.
699*ef5ccd6cSJohn Marino    LEN is the number of characters in it.  */
700*ef5ccd6cSJohn Marino 
701*ef5ccd6cSJohn Marino /* FIXME: Needs some error checking for the float case.  */
702*ef5ccd6cSJohn Marino /* FIXME(dje): IWBN to use c-exp.y's parse_number if we could.
703*ef5ccd6cSJohn Marino    That will require moving the guts into a function that we both call
704*ef5ccd6cSJohn Marino    as our YYSTYPE is different than c-exp.y's  */
705*ef5ccd6cSJohn Marino 
706*ef5ccd6cSJohn Marino static int
parse_number(char * p,int len,int parsed_float,YYSTYPE * putithere)707*ef5ccd6cSJohn Marino parse_number (char *p, int len, int parsed_float, YYSTYPE *putithere)
708*ef5ccd6cSJohn Marino {
709*ef5ccd6cSJohn Marino   /* FIXME: Shouldn't these be unsigned?  We don't deal with negative values
710*ef5ccd6cSJohn Marino      here, and we do kind of silly things like cast to unsigned.  */
711*ef5ccd6cSJohn Marino   LONGEST n = 0;
712*ef5ccd6cSJohn Marino   LONGEST prevn = 0;
713*ef5ccd6cSJohn Marino   ULONGEST un;
714*ef5ccd6cSJohn Marino 
715*ef5ccd6cSJohn Marino   int i = 0;
716*ef5ccd6cSJohn Marino   int c;
717*ef5ccd6cSJohn Marino   int base = input_radix;
718*ef5ccd6cSJohn Marino   int unsigned_p = 0;
719*ef5ccd6cSJohn Marino 
720*ef5ccd6cSJohn Marino   /* Number of "L" suffixes encountered.  */
721*ef5ccd6cSJohn Marino   int long_p = 0;
722*ef5ccd6cSJohn Marino 
723*ef5ccd6cSJohn Marino   /* We have found a "L" or "U" suffix.  */
724*ef5ccd6cSJohn Marino   int found_suffix = 0;
725*ef5ccd6cSJohn Marino 
726*ef5ccd6cSJohn Marino   ULONGEST high_bit;
727*ef5ccd6cSJohn Marino   struct type *signed_type;
728*ef5ccd6cSJohn Marino   struct type *unsigned_type;
729*ef5ccd6cSJohn Marino 
730*ef5ccd6cSJohn Marino   if (parsed_float)
731*ef5ccd6cSJohn Marino     {
732*ef5ccd6cSJohn Marino       if (! parse_go_float (parse_gdbarch, p, len,
733*ef5ccd6cSJohn Marino 			    &putithere->typed_val_float.dval,
734*ef5ccd6cSJohn Marino 			    &putithere->typed_val_float.type))
735*ef5ccd6cSJohn Marino 	return ERROR;
736*ef5ccd6cSJohn Marino       return FLOAT;
737*ef5ccd6cSJohn Marino     }
738*ef5ccd6cSJohn Marino 
739*ef5ccd6cSJohn Marino   /* Handle base-switching prefixes 0x, 0t, 0d, 0.  */
740*ef5ccd6cSJohn Marino   if (p[0] == '0')
741*ef5ccd6cSJohn Marino     switch (p[1])
742*ef5ccd6cSJohn Marino       {
743*ef5ccd6cSJohn Marino       case 'x':
744*ef5ccd6cSJohn Marino       case 'X':
745*ef5ccd6cSJohn Marino 	if (len >= 3)
746*ef5ccd6cSJohn Marino 	  {
747*ef5ccd6cSJohn Marino 	    p += 2;
748*ef5ccd6cSJohn Marino 	    base = 16;
749*ef5ccd6cSJohn Marino 	    len -= 2;
750*ef5ccd6cSJohn Marino 	  }
751*ef5ccd6cSJohn Marino 	break;
752*ef5ccd6cSJohn Marino 
753*ef5ccd6cSJohn Marino       case 'b':
754*ef5ccd6cSJohn Marino       case 'B':
755*ef5ccd6cSJohn Marino 	if (len >= 3)
756*ef5ccd6cSJohn Marino 	  {
757*ef5ccd6cSJohn Marino 	    p += 2;
758*ef5ccd6cSJohn Marino 	    base = 2;
759*ef5ccd6cSJohn Marino 	    len -= 2;
760*ef5ccd6cSJohn Marino 	  }
761*ef5ccd6cSJohn Marino 	break;
762*ef5ccd6cSJohn Marino 
763*ef5ccd6cSJohn Marino       case 't':
764*ef5ccd6cSJohn Marino       case 'T':
765*ef5ccd6cSJohn Marino       case 'd':
766*ef5ccd6cSJohn Marino       case 'D':
767*ef5ccd6cSJohn Marino 	if (len >= 3)
768*ef5ccd6cSJohn Marino 	  {
769*ef5ccd6cSJohn Marino 	    p += 2;
770*ef5ccd6cSJohn Marino 	    base = 10;
771*ef5ccd6cSJohn Marino 	    len -= 2;
772*ef5ccd6cSJohn Marino 	  }
773*ef5ccd6cSJohn Marino 	break;
774*ef5ccd6cSJohn Marino 
775*ef5ccd6cSJohn Marino       default:
776*ef5ccd6cSJohn Marino 	base = 8;
777*ef5ccd6cSJohn Marino 	break;
778*ef5ccd6cSJohn Marino       }
779*ef5ccd6cSJohn Marino 
780*ef5ccd6cSJohn Marino   while (len-- > 0)
781*ef5ccd6cSJohn Marino     {
782*ef5ccd6cSJohn Marino       c = *p++;
783*ef5ccd6cSJohn Marino       if (c >= 'A' && c <= 'Z')
784*ef5ccd6cSJohn Marino 	c += 'a' - 'A';
785*ef5ccd6cSJohn Marino       if (c != 'l' && c != 'u')
786*ef5ccd6cSJohn Marino 	n *= base;
787*ef5ccd6cSJohn Marino       if (c >= '0' && c <= '9')
788*ef5ccd6cSJohn Marino 	{
789*ef5ccd6cSJohn Marino 	  if (found_suffix)
790*ef5ccd6cSJohn Marino 	    return ERROR;
791*ef5ccd6cSJohn Marino 	  n += i = c - '0';
792*ef5ccd6cSJohn Marino 	}
793*ef5ccd6cSJohn Marino       else
794*ef5ccd6cSJohn Marino 	{
795*ef5ccd6cSJohn Marino 	  if (base > 10 && c >= 'a' && c <= 'f')
796*ef5ccd6cSJohn Marino 	    {
797*ef5ccd6cSJohn Marino 	      if (found_suffix)
798*ef5ccd6cSJohn Marino 		return ERROR;
799*ef5ccd6cSJohn Marino 	      n += i = c - 'a' + 10;
800*ef5ccd6cSJohn Marino 	    }
801*ef5ccd6cSJohn Marino 	  else if (c == 'l')
802*ef5ccd6cSJohn Marino 	    {
803*ef5ccd6cSJohn Marino 	      ++long_p;
804*ef5ccd6cSJohn Marino 	      found_suffix = 1;
805*ef5ccd6cSJohn Marino 	    }
806*ef5ccd6cSJohn Marino 	  else if (c == 'u')
807*ef5ccd6cSJohn Marino 	    {
808*ef5ccd6cSJohn Marino 	      unsigned_p = 1;
809*ef5ccd6cSJohn Marino 	      found_suffix = 1;
810*ef5ccd6cSJohn Marino 	    }
811*ef5ccd6cSJohn Marino 	  else
812*ef5ccd6cSJohn Marino 	    return ERROR;	/* Char not a digit */
813*ef5ccd6cSJohn Marino 	}
814*ef5ccd6cSJohn Marino       if (i >= base)
815*ef5ccd6cSJohn Marino 	return ERROR;		/* Invalid digit in this base.  */
816*ef5ccd6cSJohn Marino 
817*ef5ccd6cSJohn Marino       /* Portably test for overflow (only works for nonzero values, so make
818*ef5ccd6cSJohn Marino 	 a second check for zero).  FIXME: Can't we just make n and prevn
819*ef5ccd6cSJohn Marino 	 unsigned and avoid this?  */
820*ef5ccd6cSJohn Marino       if (c != 'l' && c != 'u' && (prevn >= n) && n != 0)
821*ef5ccd6cSJohn Marino 	unsigned_p = 1;		/* Try something unsigned.  */
822*ef5ccd6cSJohn Marino 
823*ef5ccd6cSJohn Marino       /* Portably test for unsigned overflow.
824*ef5ccd6cSJohn Marino 	 FIXME: This check is wrong; for example it doesn't find overflow
825*ef5ccd6cSJohn Marino 	 on 0x123456789 when LONGEST is 32 bits.  */
826*ef5ccd6cSJohn Marino       if (c != 'l' && c != 'u' && n != 0)
827*ef5ccd6cSJohn Marino 	{
828*ef5ccd6cSJohn Marino 	  if ((unsigned_p && (ULONGEST) prevn >= (ULONGEST) n))
829*ef5ccd6cSJohn Marino 	    error (_("Numeric constant too large."));
830*ef5ccd6cSJohn Marino 	}
831*ef5ccd6cSJohn Marino       prevn = n;
832*ef5ccd6cSJohn Marino     }
833*ef5ccd6cSJohn Marino 
834*ef5ccd6cSJohn Marino   /* An integer constant is an int, a long, or a long long.  An L
835*ef5ccd6cSJohn Marino      suffix forces it to be long; an LL suffix forces it to be long
836*ef5ccd6cSJohn Marino      long.  If not forced to a larger size, it gets the first type of
837*ef5ccd6cSJohn Marino      the above that it fits in.  To figure out whether it fits, we
838*ef5ccd6cSJohn Marino      shift it right and see whether anything remains.  Note that we
839*ef5ccd6cSJohn Marino      can't shift sizeof (LONGEST) * HOST_CHAR_BIT bits or more in one
840*ef5ccd6cSJohn Marino      operation, because many compilers will warn about such a shift
841*ef5ccd6cSJohn Marino      (which always produces a zero result).  Sometimes gdbarch_int_bit
842*ef5ccd6cSJohn Marino      or gdbarch_long_bit will be that big, sometimes not.  To deal with
843*ef5ccd6cSJohn Marino      the case where it is we just always shift the value more than
844*ef5ccd6cSJohn Marino      once, with fewer bits each time.  */
845*ef5ccd6cSJohn Marino 
846*ef5ccd6cSJohn Marino   un = (ULONGEST)n >> 2;
847*ef5ccd6cSJohn Marino   if (long_p == 0
848*ef5ccd6cSJohn Marino       && (un >> (gdbarch_int_bit (parse_gdbarch) - 2)) == 0)
849*ef5ccd6cSJohn Marino     {
850*ef5ccd6cSJohn Marino       high_bit = ((ULONGEST)1) << (gdbarch_int_bit (parse_gdbarch) - 1);
851*ef5ccd6cSJohn Marino 
852*ef5ccd6cSJohn Marino       /* A large decimal (not hex or octal) constant (between INT_MAX
853*ef5ccd6cSJohn Marino 	 and UINT_MAX) is a long or unsigned long, according to ANSI,
854*ef5ccd6cSJohn Marino 	 never an unsigned int, but this code treats it as unsigned
855*ef5ccd6cSJohn Marino 	 int.  This probably should be fixed.  GCC gives a warning on
856*ef5ccd6cSJohn Marino 	 such constants.  */
857*ef5ccd6cSJohn Marino 
858*ef5ccd6cSJohn Marino       unsigned_type = parse_type->builtin_unsigned_int;
859*ef5ccd6cSJohn Marino       signed_type = parse_type->builtin_int;
860*ef5ccd6cSJohn Marino     }
861*ef5ccd6cSJohn Marino   else if (long_p <= 1
862*ef5ccd6cSJohn Marino 	   && (un >> (gdbarch_long_bit (parse_gdbarch) - 2)) == 0)
863*ef5ccd6cSJohn Marino     {
864*ef5ccd6cSJohn Marino       high_bit = ((ULONGEST)1) << (gdbarch_long_bit (parse_gdbarch) - 1);
865*ef5ccd6cSJohn Marino       unsigned_type = parse_type->builtin_unsigned_long;
866*ef5ccd6cSJohn Marino       signed_type = parse_type->builtin_long;
867*ef5ccd6cSJohn Marino     }
868*ef5ccd6cSJohn Marino   else
869*ef5ccd6cSJohn Marino     {
870*ef5ccd6cSJohn Marino       int shift;
871*ef5ccd6cSJohn Marino       if (sizeof (ULONGEST) * HOST_CHAR_BIT
872*ef5ccd6cSJohn Marino 	  < gdbarch_long_long_bit (parse_gdbarch))
873*ef5ccd6cSJohn Marino 	/* A long long does not fit in a LONGEST.  */
874*ef5ccd6cSJohn Marino 	shift = (sizeof (ULONGEST) * HOST_CHAR_BIT - 1);
875*ef5ccd6cSJohn Marino       else
876*ef5ccd6cSJohn Marino 	shift = (gdbarch_long_long_bit (parse_gdbarch) - 1);
877*ef5ccd6cSJohn Marino       high_bit = (ULONGEST) 1 << shift;
878*ef5ccd6cSJohn Marino       unsigned_type = parse_type->builtin_unsigned_long_long;
879*ef5ccd6cSJohn Marino       signed_type = parse_type->builtin_long_long;
880*ef5ccd6cSJohn Marino     }
881*ef5ccd6cSJohn Marino 
882*ef5ccd6cSJohn Marino    putithere->typed_val_int.val = n;
883*ef5ccd6cSJohn Marino 
884*ef5ccd6cSJohn Marino    /* If the high bit of the worked out type is set then this number
885*ef5ccd6cSJohn Marino       has to be unsigned.  */
886*ef5ccd6cSJohn Marino 
887*ef5ccd6cSJohn Marino    if (unsigned_p || (n & high_bit))
888*ef5ccd6cSJohn Marino      {
889*ef5ccd6cSJohn Marino        putithere->typed_val_int.type = unsigned_type;
890*ef5ccd6cSJohn Marino      }
891*ef5ccd6cSJohn Marino    else
892*ef5ccd6cSJohn Marino      {
893*ef5ccd6cSJohn Marino        putithere->typed_val_int.type = signed_type;
894*ef5ccd6cSJohn Marino      }
895*ef5ccd6cSJohn Marino 
896*ef5ccd6cSJohn Marino    return INT;
897*ef5ccd6cSJohn Marino }
898*ef5ccd6cSJohn Marino 
899*ef5ccd6cSJohn Marino /* Temporary obstack used for holding strings.  */
900*ef5ccd6cSJohn Marino static struct obstack tempbuf;
901*ef5ccd6cSJohn Marino static int tempbuf_init;
902*ef5ccd6cSJohn Marino 
903*ef5ccd6cSJohn Marino /* Parse a string or character literal from TOKPTR.  The string or
904*ef5ccd6cSJohn Marino    character may be wide or unicode.  *OUTPTR is set to just after the
905*ef5ccd6cSJohn Marino    end of the literal in the input string.  The resulting token is
906*ef5ccd6cSJohn Marino    stored in VALUE.  This returns a token value, either STRING or
907*ef5ccd6cSJohn Marino    CHAR, depending on what was parsed.  *HOST_CHARS is set to the
908*ef5ccd6cSJohn Marino    number of host characters in the literal.  */
909*ef5ccd6cSJohn Marino 
910*ef5ccd6cSJohn Marino static int
parse_string_or_char(char * tokptr,char ** outptr,struct typed_stoken * value,int * host_chars)911*ef5ccd6cSJohn Marino parse_string_or_char (char *tokptr, char **outptr, struct typed_stoken *value,
912*ef5ccd6cSJohn Marino 		      int *host_chars)
913*ef5ccd6cSJohn Marino {
914*ef5ccd6cSJohn Marino   int quote;
915*ef5ccd6cSJohn Marino 
916*ef5ccd6cSJohn Marino   /* Build the gdb internal form of the input string in tempbuf.  Note
917*ef5ccd6cSJohn Marino      that the buffer is null byte terminated *only* for the
918*ef5ccd6cSJohn Marino      convenience of debugging gdb itself and printing the buffer
919*ef5ccd6cSJohn Marino      contents when the buffer contains no embedded nulls.  Gdb does
920*ef5ccd6cSJohn Marino      not depend upon the buffer being null byte terminated, it uses
921*ef5ccd6cSJohn Marino      the length string instead.  This allows gdb to handle C strings
922*ef5ccd6cSJohn Marino      (as well as strings in other languages) with embedded null
923*ef5ccd6cSJohn Marino      bytes */
924*ef5ccd6cSJohn Marino 
925*ef5ccd6cSJohn Marino   if (!tempbuf_init)
926*ef5ccd6cSJohn Marino     tempbuf_init = 1;
927*ef5ccd6cSJohn Marino   else
928*ef5ccd6cSJohn Marino     obstack_free (&tempbuf, NULL);
929*ef5ccd6cSJohn Marino   obstack_init (&tempbuf);
930*ef5ccd6cSJohn Marino 
931*ef5ccd6cSJohn Marino   /* Skip the quote.  */
932*ef5ccd6cSJohn Marino   quote = *tokptr;
933*ef5ccd6cSJohn Marino   ++tokptr;
934*ef5ccd6cSJohn Marino 
935*ef5ccd6cSJohn Marino   *host_chars = 0;
936*ef5ccd6cSJohn Marino 
937*ef5ccd6cSJohn Marino   while (*tokptr)
938*ef5ccd6cSJohn Marino     {
939*ef5ccd6cSJohn Marino       char c = *tokptr;
940*ef5ccd6cSJohn Marino       if (c == '\\')
941*ef5ccd6cSJohn Marino 	{
942*ef5ccd6cSJohn Marino 	  ++tokptr;
943*ef5ccd6cSJohn Marino 	  *host_chars += c_parse_escape (&tokptr, &tempbuf);
944*ef5ccd6cSJohn Marino 	}
945*ef5ccd6cSJohn Marino       else if (c == quote)
946*ef5ccd6cSJohn Marino 	break;
947*ef5ccd6cSJohn Marino       else
948*ef5ccd6cSJohn Marino 	{
949*ef5ccd6cSJohn Marino 	  obstack_1grow (&tempbuf, c);
950*ef5ccd6cSJohn Marino 	  ++tokptr;
951*ef5ccd6cSJohn Marino 	  /* FIXME: this does the wrong thing with multi-byte host
952*ef5ccd6cSJohn Marino 	     characters.  We could use mbrlen here, but that would
953*ef5ccd6cSJohn Marino 	     make "set host-charset" a bit less useful.  */
954*ef5ccd6cSJohn Marino 	  ++*host_chars;
955*ef5ccd6cSJohn Marino 	}
956*ef5ccd6cSJohn Marino     }
957*ef5ccd6cSJohn Marino 
958*ef5ccd6cSJohn Marino   if (*tokptr != quote)
959*ef5ccd6cSJohn Marino     {
960*ef5ccd6cSJohn Marino       if (quote == '"')
961*ef5ccd6cSJohn Marino 	error (_("Unterminated string in expression."));
962*ef5ccd6cSJohn Marino       else
963*ef5ccd6cSJohn Marino 	error (_("Unmatched single quote."));
964*ef5ccd6cSJohn Marino     }
965*ef5ccd6cSJohn Marino   ++tokptr;
966*ef5ccd6cSJohn Marino 
967*ef5ccd6cSJohn Marino   value->type = C_STRING | (quote == '\'' ? C_CHAR : 0); /*FIXME*/
968*ef5ccd6cSJohn Marino   value->ptr = obstack_base (&tempbuf);
969*ef5ccd6cSJohn Marino   value->length = obstack_object_size (&tempbuf);
970*ef5ccd6cSJohn Marino 
971*ef5ccd6cSJohn Marino   *outptr = tokptr;
972*ef5ccd6cSJohn Marino 
973*ef5ccd6cSJohn Marino   return quote == '\'' ? CHAR : STRING;
974*ef5ccd6cSJohn Marino }
975*ef5ccd6cSJohn Marino 
976*ef5ccd6cSJohn Marino struct token
977*ef5ccd6cSJohn Marino {
978*ef5ccd6cSJohn Marino   char *operator;
979*ef5ccd6cSJohn Marino   int token;
980*ef5ccd6cSJohn Marino   enum exp_opcode opcode;
981*ef5ccd6cSJohn Marino };
982*ef5ccd6cSJohn Marino 
983*ef5ccd6cSJohn Marino static const struct token tokentab3[] =
984*ef5ccd6cSJohn Marino   {
985*ef5ccd6cSJohn Marino     {">>=", ASSIGN_MODIFY, BINOP_RSH},
986*ef5ccd6cSJohn Marino     {"<<=", ASSIGN_MODIFY, BINOP_LSH},
987*ef5ccd6cSJohn Marino     /*{"&^=", ASSIGN_MODIFY, BINOP_BITWISE_ANDNOT}, TODO */
988*ef5ccd6cSJohn Marino     {"...", DOTDOTDOT, OP_NULL},
989*ef5ccd6cSJohn Marino   };
990*ef5ccd6cSJohn Marino 
991*ef5ccd6cSJohn Marino static const struct token tokentab2[] =
992*ef5ccd6cSJohn Marino   {
993*ef5ccd6cSJohn Marino     {"+=", ASSIGN_MODIFY, BINOP_ADD},
994*ef5ccd6cSJohn Marino     {"-=", ASSIGN_MODIFY, BINOP_SUB},
995*ef5ccd6cSJohn Marino     {"*=", ASSIGN_MODIFY, BINOP_MUL},
996*ef5ccd6cSJohn Marino     {"/=", ASSIGN_MODIFY, BINOP_DIV},
997*ef5ccd6cSJohn Marino     {"%=", ASSIGN_MODIFY, BINOP_REM},
998*ef5ccd6cSJohn Marino     {"|=", ASSIGN_MODIFY, BINOP_BITWISE_IOR},
999*ef5ccd6cSJohn Marino     {"&=", ASSIGN_MODIFY, BINOP_BITWISE_AND},
1000*ef5ccd6cSJohn Marino     {"^=", ASSIGN_MODIFY, BINOP_BITWISE_XOR},
1001*ef5ccd6cSJohn Marino     {"++", INCREMENT, BINOP_END},
1002*ef5ccd6cSJohn Marino     {"--", DECREMENT, BINOP_END},
1003*ef5ccd6cSJohn Marino     /*{"->", RIGHT_ARROW, BINOP_END}, Doesn't exist in Go.  */
1004*ef5ccd6cSJohn Marino     {"<-", LEFT_ARROW, BINOP_END},
1005*ef5ccd6cSJohn Marino     {"&&", ANDAND, BINOP_END},
1006*ef5ccd6cSJohn Marino     {"||", OROR, BINOP_END},
1007*ef5ccd6cSJohn Marino     {"<<", LSH, BINOP_END},
1008*ef5ccd6cSJohn Marino     {">>", RSH, BINOP_END},
1009*ef5ccd6cSJohn Marino     {"==", EQUAL, BINOP_END},
1010*ef5ccd6cSJohn Marino     {"!=", NOTEQUAL, BINOP_END},
1011*ef5ccd6cSJohn Marino     {"<=", LEQ, BINOP_END},
1012*ef5ccd6cSJohn Marino     {">=", GEQ, BINOP_END},
1013*ef5ccd6cSJohn Marino     /*{"&^", ANDNOT, BINOP_END}, TODO */
1014*ef5ccd6cSJohn Marino   };
1015*ef5ccd6cSJohn Marino 
1016*ef5ccd6cSJohn Marino /* Identifier-like tokens.  */
1017*ef5ccd6cSJohn Marino static const struct token ident_tokens[] =
1018*ef5ccd6cSJohn Marino   {
1019*ef5ccd6cSJohn Marino     {"true", TRUE_KEYWORD, OP_NULL},
1020*ef5ccd6cSJohn Marino     {"false", FALSE_KEYWORD, OP_NULL},
1021*ef5ccd6cSJohn Marino     {"nil", NIL_KEYWORD, OP_NULL},
1022*ef5ccd6cSJohn Marino     {"const", CONST_KEYWORD, OP_NULL},
1023*ef5ccd6cSJohn Marino     {"struct", STRUCT_KEYWORD, OP_NULL},
1024*ef5ccd6cSJohn Marino     {"type", TYPE_KEYWORD, OP_NULL},
1025*ef5ccd6cSJohn Marino     {"interface", INTERFACE_KEYWORD, OP_NULL},
1026*ef5ccd6cSJohn Marino     {"chan", CHAN_KEYWORD, OP_NULL},
1027*ef5ccd6cSJohn Marino     {"byte", BYTE_KEYWORD, OP_NULL}, /* An alias of uint8.  */
1028*ef5ccd6cSJohn Marino     {"len", LEN_KEYWORD, OP_NULL},
1029*ef5ccd6cSJohn Marino     {"cap", CAP_KEYWORD, OP_NULL},
1030*ef5ccd6cSJohn Marino     {"new", NEW_KEYWORD, OP_NULL},
1031*ef5ccd6cSJohn Marino     {"iota", IOTA_KEYWORD, OP_NULL},
1032*ef5ccd6cSJohn Marino   };
1033*ef5ccd6cSJohn Marino 
1034*ef5ccd6cSJohn Marino /* This is set if a NAME token appeared at the very end of the input
1035*ef5ccd6cSJohn Marino    string, with no whitespace separating the name from the EOF.  This
1036*ef5ccd6cSJohn Marino    is used only when parsing to do field name completion.  */
1037*ef5ccd6cSJohn Marino static int saw_name_at_eof;
1038*ef5ccd6cSJohn Marino 
1039*ef5ccd6cSJohn Marino /* This is set if the previously-returned token was a structure
1040*ef5ccd6cSJohn Marino    operator -- either '.' or ARROW.  This is used only when parsing to
1041*ef5ccd6cSJohn Marino    do field name completion.  */
1042*ef5ccd6cSJohn Marino static int last_was_structop;
1043*ef5ccd6cSJohn Marino 
1044*ef5ccd6cSJohn Marino /* Read one token, getting characters through lexptr.  */
1045*ef5ccd6cSJohn Marino 
1046*ef5ccd6cSJohn Marino static int
lex_one_token(void)1047*ef5ccd6cSJohn Marino lex_one_token (void)
1048*ef5ccd6cSJohn Marino {
1049*ef5ccd6cSJohn Marino   int c;
1050*ef5ccd6cSJohn Marino   int namelen;
1051*ef5ccd6cSJohn Marino   unsigned int i;
1052*ef5ccd6cSJohn Marino   char *tokstart;
1053*ef5ccd6cSJohn Marino   int saw_structop = last_was_structop;
1054*ef5ccd6cSJohn Marino   char *copy;
1055*ef5ccd6cSJohn Marino 
1056*ef5ccd6cSJohn Marino   last_was_structop = 0;
1057*ef5ccd6cSJohn Marino 
1058*ef5ccd6cSJohn Marino  retry:
1059*ef5ccd6cSJohn Marino 
1060*ef5ccd6cSJohn Marino   prev_lexptr = lexptr;
1061*ef5ccd6cSJohn Marino 
1062*ef5ccd6cSJohn Marino   tokstart = lexptr;
1063*ef5ccd6cSJohn Marino   /* See if it is a special token of length 3.  */
1064*ef5ccd6cSJohn Marino   for (i = 0; i < sizeof (tokentab3) / sizeof (tokentab3[0]); i++)
1065*ef5ccd6cSJohn Marino     if (strncmp (tokstart, tokentab3[i].operator, 3) == 0)
1066*ef5ccd6cSJohn Marino       {
1067*ef5ccd6cSJohn Marino 	lexptr += 3;
1068*ef5ccd6cSJohn Marino 	yylval.opcode = tokentab3[i].opcode;
1069*ef5ccd6cSJohn Marino 	return tokentab3[i].token;
1070*ef5ccd6cSJohn Marino       }
1071*ef5ccd6cSJohn Marino 
1072*ef5ccd6cSJohn Marino   /* See if it is a special token of length 2.  */
1073*ef5ccd6cSJohn Marino   for (i = 0; i < sizeof (tokentab2) / sizeof (tokentab2[0]); i++)
1074*ef5ccd6cSJohn Marino     if (strncmp (tokstart, tokentab2[i].operator, 2) == 0)
1075*ef5ccd6cSJohn Marino       {
1076*ef5ccd6cSJohn Marino 	lexptr += 2;
1077*ef5ccd6cSJohn Marino 	yylval.opcode = tokentab2[i].opcode;
1078*ef5ccd6cSJohn Marino 	/* NOTE: -> doesn't exist in Go, so we don't need to watch for
1079*ef5ccd6cSJohn Marino 	   setting last_was_structop here.  */
1080*ef5ccd6cSJohn Marino 	return tokentab2[i].token;
1081*ef5ccd6cSJohn Marino       }
1082*ef5ccd6cSJohn Marino 
1083*ef5ccd6cSJohn Marino   switch (c = *tokstart)
1084*ef5ccd6cSJohn Marino     {
1085*ef5ccd6cSJohn Marino     case 0:
1086*ef5ccd6cSJohn Marino       if (saw_name_at_eof)
1087*ef5ccd6cSJohn Marino 	{
1088*ef5ccd6cSJohn Marino 	  saw_name_at_eof = 0;
1089*ef5ccd6cSJohn Marino 	  return COMPLETE;
1090*ef5ccd6cSJohn Marino 	}
1091*ef5ccd6cSJohn Marino       else if (saw_structop)
1092*ef5ccd6cSJohn Marino 	return COMPLETE;
1093*ef5ccd6cSJohn Marino       else
1094*ef5ccd6cSJohn Marino         return 0;
1095*ef5ccd6cSJohn Marino 
1096*ef5ccd6cSJohn Marino     case ' ':
1097*ef5ccd6cSJohn Marino     case '\t':
1098*ef5ccd6cSJohn Marino     case '\n':
1099*ef5ccd6cSJohn Marino       lexptr++;
1100*ef5ccd6cSJohn Marino       goto retry;
1101*ef5ccd6cSJohn Marino 
1102*ef5ccd6cSJohn Marino     case '[':
1103*ef5ccd6cSJohn Marino     case '(':
1104*ef5ccd6cSJohn Marino       paren_depth++;
1105*ef5ccd6cSJohn Marino       lexptr++;
1106*ef5ccd6cSJohn Marino       return c;
1107*ef5ccd6cSJohn Marino 
1108*ef5ccd6cSJohn Marino     case ']':
1109*ef5ccd6cSJohn Marino     case ')':
1110*ef5ccd6cSJohn Marino       if (paren_depth == 0)
1111*ef5ccd6cSJohn Marino 	return 0;
1112*ef5ccd6cSJohn Marino       paren_depth--;
1113*ef5ccd6cSJohn Marino       lexptr++;
1114*ef5ccd6cSJohn Marino       return c;
1115*ef5ccd6cSJohn Marino 
1116*ef5ccd6cSJohn Marino     case ',':
1117*ef5ccd6cSJohn Marino       if (comma_terminates
1118*ef5ccd6cSJohn Marino           && paren_depth == 0)
1119*ef5ccd6cSJohn Marino 	return 0;
1120*ef5ccd6cSJohn Marino       lexptr++;
1121*ef5ccd6cSJohn Marino       return c;
1122*ef5ccd6cSJohn Marino 
1123*ef5ccd6cSJohn Marino     case '.':
1124*ef5ccd6cSJohn Marino       /* Might be a floating point number.  */
1125*ef5ccd6cSJohn Marino       if (lexptr[1] < '0' || lexptr[1] > '9')
1126*ef5ccd6cSJohn Marino 	{
1127*ef5ccd6cSJohn Marino 	  if (parse_completion)
1128*ef5ccd6cSJohn Marino 	    last_was_structop = 1;
1129*ef5ccd6cSJohn Marino 	  goto symbol;		/* Nope, must be a symbol. */
1130*ef5ccd6cSJohn Marino 	}
1131*ef5ccd6cSJohn Marino       /* FALL THRU into number case.  */
1132*ef5ccd6cSJohn Marino 
1133*ef5ccd6cSJohn Marino     case '0':
1134*ef5ccd6cSJohn Marino     case '1':
1135*ef5ccd6cSJohn Marino     case '2':
1136*ef5ccd6cSJohn Marino     case '3':
1137*ef5ccd6cSJohn Marino     case '4':
1138*ef5ccd6cSJohn Marino     case '5':
1139*ef5ccd6cSJohn Marino     case '6':
1140*ef5ccd6cSJohn Marino     case '7':
1141*ef5ccd6cSJohn Marino     case '8':
1142*ef5ccd6cSJohn Marino     case '9':
1143*ef5ccd6cSJohn Marino       {
1144*ef5ccd6cSJohn Marino 	/* It's a number.  */
1145*ef5ccd6cSJohn Marino 	int got_dot = 0, got_e = 0, toktype;
1146*ef5ccd6cSJohn Marino 	char *p = tokstart;
1147*ef5ccd6cSJohn Marino 	int hex = input_radix > 10;
1148*ef5ccd6cSJohn Marino 
1149*ef5ccd6cSJohn Marino 	if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1150*ef5ccd6cSJohn Marino 	  {
1151*ef5ccd6cSJohn Marino 	    p += 2;
1152*ef5ccd6cSJohn Marino 	    hex = 1;
1153*ef5ccd6cSJohn Marino 	  }
1154*ef5ccd6cSJohn Marino 
1155*ef5ccd6cSJohn Marino 	for (;; ++p)
1156*ef5ccd6cSJohn Marino 	  {
1157*ef5ccd6cSJohn Marino 	    /* This test includes !hex because 'e' is a valid hex digit
1158*ef5ccd6cSJohn Marino 	       and thus does not indicate a floating point number when
1159*ef5ccd6cSJohn Marino 	       the radix is hex.  */
1160*ef5ccd6cSJohn Marino 	    if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1161*ef5ccd6cSJohn Marino 	      got_dot = got_e = 1;
1162*ef5ccd6cSJohn Marino 	    /* This test does not include !hex, because a '.' always indicates
1163*ef5ccd6cSJohn Marino 	       a decimal floating point number regardless of the radix.  */
1164*ef5ccd6cSJohn Marino 	    else if (!got_dot && *p == '.')
1165*ef5ccd6cSJohn Marino 	      got_dot = 1;
1166*ef5ccd6cSJohn Marino 	    else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1167*ef5ccd6cSJohn Marino 		     && (*p == '-' || *p == '+'))
1168*ef5ccd6cSJohn Marino 	      /* This is the sign of the exponent, not the end of the
1169*ef5ccd6cSJohn Marino 		 number.  */
1170*ef5ccd6cSJohn Marino 	      continue;
1171*ef5ccd6cSJohn Marino 	    /* We will take any letters or digits.  parse_number will
1172*ef5ccd6cSJohn Marino 	       complain if past the radix, or if L or U are not final.  */
1173*ef5ccd6cSJohn Marino 	    else if ((*p < '0' || *p > '9')
1174*ef5ccd6cSJohn Marino 		     && ((*p < 'a' || *p > 'z')
1175*ef5ccd6cSJohn Marino 				  && (*p < 'A' || *p > 'Z')))
1176*ef5ccd6cSJohn Marino 	      break;
1177*ef5ccd6cSJohn Marino 	  }
1178*ef5ccd6cSJohn Marino 	toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1179*ef5ccd6cSJohn Marino         if (toktype == ERROR)
1180*ef5ccd6cSJohn Marino 	  {
1181*ef5ccd6cSJohn Marino 	    char *err_copy = (char *) alloca (p - tokstart + 1);
1182*ef5ccd6cSJohn Marino 
1183*ef5ccd6cSJohn Marino 	    memcpy (err_copy, tokstart, p - tokstart);
1184*ef5ccd6cSJohn Marino 	    err_copy[p - tokstart] = 0;
1185*ef5ccd6cSJohn Marino 	    error (_("Invalid number \"%s\"."), err_copy);
1186*ef5ccd6cSJohn Marino 	  }
1187*ef5ccd6cSJohn Marino 	lexptr = p;
1188*ef5ccd6cSJohn Marino 	return toktype;
1189*ef5ccd6cSJohn Marino       }
1190*ef5ccd6cSJohn Marino 
1191*ef5ccd6cSJohn Marino     case '@':
1192*ef5ccd6cSJohn Marino       {
1193*ef5ccd6cSJohn Marino 	char *p = &tokstart[1];
1194*ef5ccd6cSJohn Marino 	size_t len = strlen ("entry");
1195*ef5ccd6cSJohn Marino 
1196*ef5ccd6cSJohn Marino 	while (isspace (*p))
1197*ef5ccd6cSJohn Marino 	  p++;
1198*ef5ccd6cSJohn Marino 	if (strncmp (p, "entry", len) == 0 && !isalnum (p[len])
1199*ef5ccd6cSJohn Marino 	    && p[len] != '_')
1200*ef5ccd6cSJohn Marino 	  {
1201*ef5ccd6cSJohn Marino 	    lexptr = &p[len];
1202*ef5ccd6cSJohn Marino 	    return ENTRY;
1203*ef5ccd6cSJohn Marino 	  }
1204*ef5ccd6cSJohn Marino       }
1205*ef5ccd6cSJohn Marino       /* FALLTHRU */
1206*ef5ccd6cSJohn Marino     case '+':
1207*ef5ccd6cSJohn Marino     case '-':
1208*ef5ccd6cSJohn Marino     case '*':
1209*ef5ccd6cSJohn Marino     case '/':
1210*ef5ccd6cSJohn Marino     case '%':
1211*ef5ccd6cSJohn Marino     case '|':
1212*ef5ccd6cSJohn Marino     case '&':
1213*ef5ccd6cSJohn Marino     case '^':
1214*ef5ccd6cSJohn Marino     case '~':
1215*ef5ccd6cSJohn Marino     case '!':
1216*ef5ccd6cSJohn Marino     case '<':
1217*ef5ccd6cSJohn Marino     case '>':
1218*ef5ccd6cSJohn Marino     case '?':
1219*ef5ccd6cSJohn Marino     case ':':
1220*ef5ccd6cSJohn Marino     case '=':
1221*ef5ccd6cSJohn Marino     case '{':
1222*ef5ccd6cSJohn Marino     case '}':
1223*ef5ccd6cSJohn Marino     symbol:
1224*ef5ccd6cSJohn Marino       lexptr++;
1225*ef5ccd6cSJohn Marino       return c;
1226*ef5ccd6cSJohn Marino 
1227*ef5ccd6cSJohn Marino     case '\'':
1228*ef5ccd6cSJohn Marino     case '"':
1229*ef5ccd6cSJohn Marino     case '`':
1230*ef5ccd6cSJohn Marino       {
1231*ef5ccd6cSJohn Marino 	int host_len;
1232*ef5ccd6cSJohn Marino 	int result = parse_string_or_char (tokstart, &lexptr, &yylval.tsval,
1233*ef5ccd6cSJohn Marino 					   &host_len);
1234*ef5ccd6cSJohn Marino 	if (result == CHAR)
1235*ef5ccd6cSJohn Marino 	  {
1236*ef5ccd6cSJohn Marino 	    if (host_len == 0)
1237*ef5ccd6cSJohn Marino 	      error (_("Empty character constant."));
1238*ef5ccd6cSJohn Marino 	    else if (host_len > 2 && c == '\'')
1239*ef5ccd6cSJohn Marino 	      {
1240*ef5ccd6cSJohn Marino 		++tokstart;
1241*ef5ccd6cSJohn Marino 		namelen = lexptr - tokstart - 1;
1242*ef5ccd6cSJohn Marino 		goto tryname;
1243*ef5ccd6cSJohn Marino 	      }
1244*ef5ccd6cSJohn Marino 	    else if (host_len > 1)
1245*ef5ccd6cSJohn Marino 	      error (_("Invalid character constant."));
1246*ef5ccd6cSJohn Marino 	  }
1247*ef5ccd6cSJohn Marino 	return result;
1248*ef5ccd6cSJohn Marino       }
1249*ef5ccd6cSJohn Marino     }
1250*ef5ccd6cSJohn Marino 
1251*ef5ccd6cSJohn Marino   if (!(c == '_' || c == '$'
1252*ef5ccd6cSJohn Marino 	|| (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1253*ef5ccd6cSJohn Marino     /* We must have come across a bad character (e.g. ';').  */
1254*ef5ccd6cSJohn Marino     error (_("Invalid character '%c' in expression."), c);
1255*ef5ccd6cSJohn Marino 
1256*ef5ccd6cSJohn Marino   /* It's a name.  See how long it is.  */
1257*ef5ccd6cSJohn Marino   namelen = 0;
1258*ef5ccd6cSJohn Marino   for (c = tokstart[namelen];
1259*ef5ccd6cSJohn Marino        (c == '_' || c == '$' || (c >= '0' && c <= '9')
1260*ef5ccd6cSJohn Marino 	|| (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));)
1261*ef5ccd6cSJohn Marino     {
1262*ef5ccd6cSJohn Marino       c = tokstart[++namelen];
1263*ef5ccd6cSJohn Marino     }
1264*ef5ccd6cSJohn Marino 
1265*ef5ccd6cSJohn Marino   /* The token "if" terminates the expression and is NOT removed from
1266*ef5ccd6cSJohn Marino      the input stream.  It doesn't count if it appears in the
1267*ef5ccd6cSJohn Marino      expansion of a macro.  */
1268*ef5ccd6cSJohn Marino   if (namelen == 2
1269*ef5ccd6cSJohn Marino       && tokstart[0] == 'i'
1270*ef5ccd6cSJohn Marino       && tokstart[1] == 'f')
1271*ef5ccd6cSJohn Marino     {
1272*ef5ccd6cSJohn Marino       return 0;
1273*ef5ccd6cSJohn Marino     }
1274*ef5ccd6cSJohn Marino 
1275*ef5ccd6cSJohn Marino   /* For the same reason (breakpoint conditions), "thread N"
1276*ef5ccd6cSJohn Marino      terminates the expression.  "thread" could be an identifier, but
1277*ef5ccd6cSJohn Marino      an identifier is never followed by a number without intervening
1278*ef5ccd6cSJohn Marino      punctuation.
1279*ef5ccd6cSJohn Marino      Handle abbreviations of these, similarly to
1280*ef5ccd6cSJohn Marino      breakpoint.c:find_condition_and_thread.
1281*ef5ccd6cSJohn Marino      TODO: Watch for "goroutine" here?  */
1282*ef5ccd6cSJohn Marino   if (namelen >= 1
1283*ef5ccd6cSJohn Marino       && strncmp (tokstart, "thread", namelen) == 0
1284*ef5ccd6cSJohn Marino       && (tokstart[namelen] == ' ' || tokstart[namelen] == '\t'))
1285*ef5ccd6cSJohn Marino     {
1286*ef5ccd6cSJohn Marino       char *p = tokstart + namelen + 1;
1287*ef5ccd6cSJohn Marino       while (*p == ' ' || *p == '\t')
1288*ef5ccd6cSJohn Marino 	p++;
1289*ef5ccd6cSJohn Marino       if (*p >= '0' && *p <= '9')
1290*ef5ccd6cSJohn Marino 	return 0;
1291*ef5ccd6cSJohn Marino     }
1292*ef5ccd6cSJohn Marino 
1293*ef5ccd6cSJohn Marino   lexptr += namelen;
1294*ef5ccd6cSJohn Marino 
1295*ef5ccd6cSJohn Marino   tryname:
1296*ef5ccd6cSJohn Marino 
1297*ef5ccd6cSJohn Marino   yylval.sval.ptr = tokstart;
1298*ef5ccd6cSJohn Marino   yylval.sval.length = namelen;
1299*ef5ccd6cSJohn Marino 
1300*ef5ccd6cSJohn Marino   /* Catch specific keywords.  */
1301*ef5ccd6cSJohn Marino   copy = copy_name (yylval.sval);
1302*ef5ccd6cSJohn Marino   for (i = 0; i < sizeof (ident_tokens) / sizeof (ident_tokens[0]); i++)
1303*ef5ccd6cSJohn Marino     if (strcmp (copy, ident_tokens[i].operator) == 0)
1304*ef5ccd6cSJohn Marino       {
1305*ef5ccd6cSJohn Marino 	/* It is ok to always set this, even though we don't always
1306*ef5ccd6cSJohn Marino 	   strictly need to.  */
1307*ef5ccd6cSJohn Marino 	yylval.opcode = ident_tokens[i].opcode;
1308*ef5ccd6cSJohn Marino 	return ident_tokens[i].token;
1309*ef5ccd6cSJohn Marino       }
1310*ef5ccd6cSJohn Marino 
1311*ef5ccd6cSJohn Marino   if (*tokstart == '$')
1312*ef5ccd6cSJohn Marino     return DOLLAR_VARIABLE;
1313*ef5ccd6cSJohn Marino 
1314*ef5ccd6cSJohn Marino   if (parse_completion && *lexptr == '\0')
1315*ef5ccd6cSJohn Marino     saw_name_at_eof = 1;
1316*ef5ccd6cSJohn Marino   return NAME;
1317*ef5ccd6cSJohn Marino }
1318*ef5ccd6cSJohn Marino 
1319*ef5ccd6cSJohn Marino /* An object of this type is pushed on a FIFO by the "outer" lexer.  */
1320*ef5ccd6cSJohn Marino typedef struct
1321*ef5ccd6cSJohn Marino {
1322*ef5ccd6cSJohn Marino   int token;
1323*ef5ccd6cSJohn Marino   YYSTYPE value;
1324*ef5ccd6cSJohn Marino } token_and_value;
1325*ef5ccd6cSJohn Marino 
1326*ef5ccd6cSJohn Marino DEF_VEC_O (token_and_value);
1327*ef5ccd6cSJohn Marino 
1328*ef5ccd6cSJohn Marino /* A FIFO of tokens that have been read but not yet returned to the
1329*ef5ccd6cSJohn Marino    parser.  */
1330*ef5ccd6cSJohn Marino static VEC (token_and_value) *token_fifo;
1331*ef5ccd6cSJohn Marino 
1332*ef5ccd6cSJohn Marino /* Non-zero if the lexer should return tokens from the FIFO.  */
1333*ef5ccd6cSJohn Marino static int popping;
1334*ef5ccd6cSJohn Marino 
1335*ef5ccd6cSJohn Marino /* Temporary storage for yylex; this holds symbol names as they are
1336*ef5ccd6cSJohn Marino    built up.  */
1337*ef5ccd6cSJohn Marino static struct obstack name_obstack;
1338*ef5ccd6cSJohn Marino 
1339*ef5ccd6cSJohn Marino /* Build "package.name" in name_obstack.
1340*ef5ccd6cSJohn Marino    For convenience of the caller, the name is NUL-terminated,
1341*ef5ccd6cSJohn Marino    but the NUL is not included in the recorded length.  */
1342*ef5ccd6cSJohn Marino 
1343*ef5ccd6cSJohn Marino static struct stoken
build_packaged_name(const char * package,int package_len,const char * name,int name_len)1344*ef5ccd6cSJohn Marino build_packaged_name (const char *package, int package_len,
1345*ef5ccd6cSJohn Marino 		     const char *name, int name_len)
1346*ef5ccd6cSJohn Marino {
1347*ef5ccd6cSJohn Marino   struct stoken result;
1348*ef5ccd6cSJohn Marino 
1349*ef5ccd6cSJohn Marino   obstack_free (&name_obstack, obstack_base (&name_obstack));
1350*ef5ccd6cSJohn Marino   obstack_grow (&name_obstack, package, package_len);
1351*ef5ccd6cSJohn Marino   obstack_grow_str (&name_obstack, ".");
1352*ef5ccd6cSJohn Marino   obstack_grow (&name_obstack, name, name_len);
1353*ef5ccd6cSJohn Marino   obstack_grow (&name_obstack, "", 1);
1354*ef5ccd6cSJohn Marino   result.ptr = obstack_base (&name_obstack);
1355*ef5ccd6cSJohn Marino   result.length = obstack_object_size (&name_obstack) - 1;
1356*ef5ccd6cSJohn Marino 
1357*ef5ccd6cSJohn Marino   return result;
1358*ef5ccd6cSJohn Marino }
1359*ef5ccd6cSJohn Marino 
1360*ef5ccd6cSJohn Marino /* Return non-zero if NAME is a package name.
1361*ef5ccd6cSJohn Marino    BLOCK is the scope in which to interpret NAME; this can be NULL
1362*ef5ccd6cSJohn Marino    to mean the global scope.  */
1363*ef5ccd6cSJohn Marino 
1364*ef5ccd6cSJohn Marino static int
package_name_p(const char * name,const struct block * block)1365*ef5ccd6cSJohn Marino package_name_p (const char *name, const struct block *block)
1366*ef5ccd6cSJohn Marino {
1367*ef5ccd6cSJohn Marino   struct symbol *sym;
1368*ef5ccd6cSJohn Marino   struct field_of_this_result is_a_field_of_this;
1369*ef5ccd6cSJohn Marino 
1370*ef5ccd6cSJohn Marino   sym = lookup_symbol (name, block, STRUCT_DOMAIN, &is_a_field_of_this);
1371*ef5ccd6cSJohn Marino 
1372*ef5ccd6cSJohn Marino   if (sym
1373*ef5ccd6cSJohn Marino       && SYMBOL_CLASS (sym) == LOC_TYPEDEF
1374*ef5ccd6cSJohn Marino       && TYPE_CODE (SYMBOL_TYPE (sym)) == TYPE_CODE_MODULE)
1375*ef5ccd6cSJohn Marino     return 1;
1376*ef5ccd6cSJohn Marino 
1377*ef5ccd6cSJohn Marino   return 0;
1378*ef5ccd6cSJohn Marino }
1379*ef5ccd6cSJohn Marino 
1380*ef5ccd6cSJohn Marino /* Classify a (potential) function in the "unsafe" package.
1381*ef5ccd6cSJohn Marino    We fold these into "keywords" to keep things simple, at least until
1382*ef5ccd6cSJohn Marino    something more complex is warranted.  */
1383*ef5ccd6cSJohn Marino 
1384*ef5ccd6cSJohn Marino static int
classify_unsafe_function(struct stoken function_name)1385*ef5ccd6cSJohn Marino classify_unsafe_function (struct stoken function_name)
1386*ef5ccd6cSJohn Marino {
1387*ef5ccd6cSJohn Marino   char *copy = copy_name (function_name);
1388*ef5ccd6cSJohn Marino 
1389*ef5ccd6cSJohn Marino   if (strcmp (copy, "Sizeof") == 0)
1390*ef5ccd6cSJohn Marino     {
1391*ef5ccd6cSJohn Marino       yylval.sval = function_name;
1392*ef5ccd6cSJohn Marino       return SIZEOF_KEYWORD;
1393*ef5ccd6cSJohn Marino     }
1394*ef5ccd6cSJohn Marino 
1395*ef5ccd6cSJohn Marino   error (_("Unknown function in `unsafe' package: %s"), copy);
1396*ef5ccd6cSJohn Marino }
1397*ef5ccd6cSJohn Marino 
1398*ef5ccd6cSJohn Marino /* Classify token(s) "name1.name2" where name1 is known to be a package.
1399*ef5ccd6cSJohn Marino    The contents of the token are in `yylval'.
1400*ef5ccd6cSJohn Marino    Updates yylval and returns the new token type.
1401*ef5ccd6cSJohn Marino 
1402*ef5ccd6cSJohn Marino    The result is one of NAME, NAME_OR_INT, or TYPENAME.  */
1403*ef5ccd6cSJohn Marino 
1404*ef5ccd6cSJohn Marino static int
classify_packaged_name(const struct block * block)1405*ef5ccd6cSJohn Marino classify_packaged_name (const struct block *block)
1406*ef5ccd6cSJohn Marino {
1407*ef5ccd6cSJohn Marino   char *copy;
1408*ef5ccd6cSJohn Marino   struct symbol *sym;
1409*ef5ccd6cSJohn Marino   struct field_of_this_result is_a_field_of_this;
1410*ef5ccd6cSJohn Marino 
1411*ef5ccd6cSJohn Marino   copy = copy_name (yylval.sval);
1412*ef5ccd6cSJohn Marino 
1413*ef5ccd6cSJohn Marino   sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1414*ef5ccd6cSJohn Marino 
1415*ef5ccd6cSJohn Marino   if (sym)
1416*ef5ccd6cSJohn Marino     {
1417*ef5ccd6cSJohn Marino       yylval.ssym.sym = sym;
1418*ef5ccd6cSJohn Marino       yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1419*ef5ccd6cSJohn Marino     }
1420*ef5ccd6cSJohn Marino 
1421*ef5ccd6cSJohn Marino   return NAME;
1422*ef5ccd6cSJohn Marino }
1423*ef5ccd6cSJohn Marino 
1424*ef5ccd6cSJohn Marino /* Classify a NAME token.
1425*ef5ccd6cSJohn Marino    The contents of the token are in `yylval'.
1426*ef5ccd6cSJohn Marino    Updates yylval and returns the new token type.
1427*ef5ccd6cSJohn Marino    BLOCK is the block in which lookups start; this can be NULL
1428*ef5ccd6cSJohn Marino    to mean the global scope.
1429*ef5ccd6cSJohn Marino 
1430*ef5ccd6cSJohn Marino    The result is one of NAME, NAME_OR_INT, or TYPENAME.  */
1431*ef5ccd6cSJohn Marino 
1432*ef5ccd6cSJohn Marino static int
classify_name(const struct block * block)1433*ef5ccd6cSJohn Marino classify_name (const struct block *block)
1434*ef5ccd6cSJohn Marino {
1435*ef5ccd6cSJohn Marino   struct type *type;
1436*ef5ccd6cSJohn Marino   struct symbol *sym;
1437*ef5ccd6cSJohn Marino   char *copy;
1438*ef5ccd6cSJohn Marino   struct field_of_this_result is_a_field_of_this;
1439*ef5ccd6cSJohn Marino 
1440*ef5ccd6cSJohn Marino   copy = copy_name (yylval.sval);
1441*ef5ccd6cSJohn Marino 
1442*ef5ccd6cSJohn Marino   /* Try primitive types first so they win over bad/weird debug info.  */
1443*ef5ccd6cSJohn Marino   type = language_lookup_primitive_type_by_name (parse_language,
1444*ef5ccd6cSJohn Marino 						 parse_gdbarch, copy);
1445*ef5ccd6cSJohn Marino   if (type != NULL)
1446*ef5ccd6cSJohn Marino     {
1447*ef5ccd6cSJohn Marino       /* NOTE: We take advantage of the fact that yylval coming in was a
1448*ef5ccd6cSJohn Marino 	 NAME, and that struct ttype is a compatible extension of struct
1449*ef5ccd6cSJohn Marino 	 stoken, so yylval.tsym.stoken is already filled in.  */
1450*ef5ccd6cSJohn Marino       yylval.tsym.type = type;
1451*ef5ccd6cSJohn Marino       return TYPENAME;
1452*ef5ccd6cSJohn Marino     }
1453*ef5ccd6cSJohn Marino 
1454*ef5ccd6cSJohn Marino   /* TODO: What about other types?  */
1455*ef5ccd6cSJohn Marino 
1456*ef5ccd6cSJohn Marino   sym = lookup_symbol (copy, block, VAR_DOMAIN, &is_a_field_of_this);
1457*ef5ccd6cSJohn Marino 
1458*ef5ccd6cSJohn Marino   if (sym)
1459*ef5ccd6cSJohn Marino     {
1460*ef5ccd6cSJohn Marino       yylval.ssym.sym = sym;
1461*ef5ccd6cSJohn Marino       yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1462*ef5ccd6cSJohn Marino       return NAME;
1463*ef5ccd6cSJohn Marino     }
1464*ef5ccd6cSJohn Marino 
1465*ef5ccd6cSJohn Marino   /* If we didn't find a symbol, look again in the current package.
1466*ef5ccd6cSJohn Marino      This is to, e.g., make "p global_var" work without having to specify
1467*ef5ccd6cSJohn Marino      the package name.  We intentionally only looks for objects in the
1468*ef5ccd6cSJohn Marino      current package.  */
1469*ef5ccd6cSJohn Marino 
1470*ef5ccd6cSJohn Marino   {
1471*ef5ccd6cSJohn Marino     char *current_package_name = go_block_package_name (block);
1472*ef5ccd6cSJohn Marino 
1473*ef5ccd6cSJohn Marino     if (current_package_name != NULL)
1474*ef5ccd6cSJohn Marino       {
1475*ef5ccd6cSJohn Marino 	struct stoken sval =
1476*ef5ccd6cSJohn Marino 	  build_packaged_name (current_package_name,
1477*ef5ccd6cSJohn Marino 			       strlen (current_package_name),
1478*ef5ccd6cSJohn Marino 			       copy, strlen (copy));
1479*ef5ccd6cSJohn Marino 
1480*ef5ccd6cSJohn Marino 	xfree (current_package_name);
1481*ef5ccd6cSJohn Marino 	sym = lookup_symbol (sval.ptr, block, VAR_DOMAIN,
1482*ef5ccd6cSJohn Marino 			     &is_a_field_of_this);
1483*ef5ccd6cSJohn Marino 	if (sym)
1484*ef5ccd6cSJohn Marino 	  {
1485*ef5ccd6cSJohn Marino 	    yylval.ssym.stoken = sval;
1486*ef5ccd6cSJohn Marino 	    yylval.ssym.sym = sym;
1487*ef5ccd6cSJohn Marino 	    yylval.ssym.is_a_field_of_this = is_a_field_of_this.type != NULL;
1488*ef5ccd6cSJohn Marino 	    return NAME;
1489*ef5ccd6cSJohn Marino 	  }
1490*ef5ccd6cSJohn Marino       }
1491*ef5ccd6cSJohn Marino   }
1492*ef5ccd6cSJohn Marino 
1493*ef5ccd6cSJohn Marino   /* Input names that aren't symbols but ARE valid hex numbers, when
1494*ef5ccd6cSJohn Marino      the input radix permits them, can be names or numbers depending
1495*ef5ccd6cSJohn Marino      on the parse.  Note we support radixes > 16 here.  */
1496*ef5ccd6cSJohn Marino   if ((copy[0] >= 'a' && copy[0] < 'a' + input_radix - 10)
1497*ef5ccd6cSJohn Marino       || (copy[0] >= 'A' && copy[0] < 'A' + input_radix - 10))
1498*ef5ccd6cSJohn Marino     {
1499*ef5ccd6cSJohn Marino       YYSTYPE newlval;	/* Its value is ignored.  */
1500*ef5ccd6cSJohn Marino       int hextype = parse_number (copy, yylval.sval.length, 0, &newlval);
1501*ef5ccd6cSJohn Marino       if (hextype == INT)
1502*ef5ccd6cSJohn Marino 	{
1503*ef5ccd6cSJohn Marino 	  yylval.ssym.sym = NULL;
1504*ef5ccd6cSJohn Marino 	  yylval.ssym.is_a_field_of_this = 0;
1505*ef5ccd6cSJohn Marino 	  return NAME_OR_INT;
1506*ef5ccd6cSJohn Marino 	}
1507*ef5ccd6cSJohn Marino     }
1508*ef5ccd6cSJohn Marino 
1509*ef5ccd6cSJohn Marino   yylval.ssym.sym = NULL;
1510*ef5ccd6cSJohn Marino   yylval.ssym.is_a_field_of_this = 0;
1511*ef5ccd6cSJohn Marino   return NAME;
1512*ef5ccd6cSJohn Marino }
1513*ef5ccd6cSJohn Marino 
1514*ef5ccd6cSJohn Marino /* This is taken from c-exp.y mostly to get something working.
1515*ef5ccd6cSJohn Marino    The basic structure has been kept because we may yet need some of it.  */
1516*ef5ccd6cSJohn Marino 
1517*ef5ccd6cSJohn Marino static int
yylex(void)1518*ef5ccd6cSJohn Marino yylex (void)
1519*ef5ccd6cSJohn Marino {
1520*ef5ccd6cSJohn Marino   token_and_value current, next;
1521*ef5ccd6cSJohn Marino 
1522*ef5ccd6cSJohn Marino   if (popping && !VEC_empty (token_and_value, token_fifo))
1523*ef5ccd6cSJohn Marino     {
1524*ef5ccd6cSJohn Marino       token_and_value tv = *VEC_index (token_and_value, token_fifo, 0);
1525*ef5ccd6cSJohn Marino       VEC_ordered_remove (token_and_value, token_fifo, 0);
1526*ef5ccd6cSJohn Marino       yylval = tv.value;
1527*ef5ccd6cSJohn Marino       /* There's no need to fall through to handle package.name
1528*ef5ccd6cSJohn Marino 	 as that can never happen here.  In theory.  */
1529*ef5ccd6cSJohn Marino       return tv.token;
1530*ef5ccd6cSJohn Marino     }
1531*ef5ccd6cSJohn Marino   popping = 0;
1532*ef5ccd6cSJohn Marino 
1533*ef5ccd6cSJohn Marino   current.token = lex_one_token ();
1534*ef5ccd6cSJohn Marino 
1535*ef5ccd6cSJohn Marino   /* TODO: Need a way to force specifying name1 as a package.
1536*ef5ccd6cSJohn Marino      .name1.name2 ?  */
1537*ef5ccd6cSJohn Marino 
1538*ef5ccd6cSJohn Marino   if (current.token != NAME)
1539*ef5ccd6cSJohn Marino     return current.token;
1540*ef5ccd6cSJohn Marino 
1541*ef5ccd6cSJohn Marino   /* See if we have "name1 . name2".  */
1542*ef5ccd6cSJohn Marino 
1543*ef5ccd6cSJohn Marino   current.value = yylval;
1544*ef5ccd6cSJohn Marino   next.token = lex_one_token ();
1545*ef5ccd6cSJohn Marino   next.value = yylval;
1546*ef5ccd6cSJohn Marino 
1547*ef5ccd6cSJohn Marino   if (next.token == '.')
1548*ef5ccd6cSJohn Marino     {
1549*ef5ccd6cSJohn Marino       token_and_value name2;
1550*ef5ccd6cSJohn Marino 
1551*ef5ccd6cSJohn Marino       name2.token = lex_one_token ();
1552*ef5ccd6cSJohn Marino       name2.value = yylval;
1553*ef5ccd6cSJohn Marino 
1554*ef5ccd6cSJohn Marino       if (name2.token == NAME)
1555*ef5ccd6cSJohn Marino 	{
1556*ef5ccd6cSJohn Marino 	  /* Ok, we have "name1 . name2".  */
1557*ef5ccd6cSJohn Marino 	  char *copy;
1558*ef5ccd6cSJohn Marino 
1559*ef5ccd6cSJohn Marino 	  copy = copy_name (current.value.sval);
1560*ef5ccd6cSJohn Marino 
1561*ef5ccd6cSJohn Marino 	  if (strcmp (copy, "unsafe") == 0)
1562*ef5ccd6cSJohn Marino 	    {
1563*ef5ccd6cSJohn Marino 	      popping = 1;
1564*ef5ccd6cSJohn Marino 	      return classify_unsafe_function (name2.value.sval);
1565*ef5ccd6cSJohn Marino 	    }
1566*ef5ccd6cSJohn Marino 
1567*ef5ccd6cSJohn Marino 	  if (package_name_p (copy, expression_context_block))
1568*ef5ccd6cSJohn Marino 	    {
1569*ef5ccd6cSJohn Marino 	      popping = 1;
1570*ef5ccd6cSJohn Marino 	      yylval.sval = build_packaged_name (current.value.sval.ptr,
1571*ef5ccd6cSJohn Marino 						 current.value.sval.length,
1572*ef5ccd6cSJohn Marino 						 name2.value.sval.ptr,
1573*ef5ccd6cSJohn Marino 						 name2.value.sval.length);
1574*ef5ccd6cSJohn Marino 	      return classify_packaged_name (expression_context_block);
1575*ef5ccd6cSJohn Marino 	    }
1576*ef5ccd6cSJohn Marino 	}
1577*ef5ccd6cSJohn Marino 
1578*ef5ccd6cSJohn Marino       VEC_safe_push (token_and_value, token_fifo, &next);
1579*ef5ccd6cSJohn Marino       VEC_safe_push (token_and_value, token_fifo, &name2);
1580*ef5ccd6cSJohn Marino     }
1581*ef5ccd6cSJohn Marino   else
1582*ef5ccd6cSJohn Marino     {
1583*ef5ccd6cSJohn Marino       VEC_safe_push (token_and_value, token_fifo, &next);
1584*ef5ccd6cSJohn Marino     }
1585*ef5ccd6cSJohn Marino 
1586*ef5ccd6cSJohn Marino   /* If we arrive here we don't have a package-qualified name.  */
1587*ef5ccd6cSJohn Marino 
1588*ef5ccd6cSJohn Marino   popping = 1;
1589*ef5ccd6cSJohn Marino   yylval = current.value;
1590*ef5ccd6cSJohn Marino   return classify_name (expression_context_block);
1591*ef5ccd6cSJohn Marino }
1592*ef5ccd6cSJohn Marino 
1593*ef5ccd6cSJohn Marino int
go_parse(void)1594*ef5ccd6cSJohn Marino go_parse (void)
1595*ef5ccd6cSJohn Marino {
1596*ef5ccd6cSJohn Marino   int result;
1597*ef5ccd6cSJohn Marino   struct cleanup *back_to = make_cleanup (null_cleanup, NULL);
1598*ef5ccd6cSJohn Marino 
1599*ef5ccd6cSJohn Marino   make_cleanup_restore_integer (&yydebug);
1600*ef5ccd6cSJohn Marino   yydebug = parser_debug;
1601*ef5ccd6cSJohn Marino 
1602*ef5ccd6cSJohn Marino   /* Initialize some state used by the lexer.  */
1603*ef5ccd6cSJohn Marino   last_was_structop = 0;
1604*ef5ccd6cSJohn Marino   saw_name_at_eof = 0;
1605*ef5ccd6cSJohn Marino 
1606*ef5ccd6cSJohn Marino   VEC_free (token_and_value, token_fifo);
1607*ef5ccd6cSJohn Marino   popping = 0;
1608*ef5ccd6cSJohn Marino   obstack_init (&name_obstack);
1609*ef5ccd6cSJohn Marino   make_cleanup_obstack_free (&name_obstack);
1610*ef5ccd6cSJohn Marino 
1611*ef5ccd6cSJohn Marino   result = yyparse ();
1612*ef5ccd6cSJohn Marino   do_cleanups (back_to);
1613*ef5ccd6cSJohn Marino   return result;
1614*ef5ccd6cSJohn Marino }
1615*ef5ccd6cSJohn Marino 
1616*ef5ccd6cSJohn Marino void
yyerror(char * msg)1617*ef5ccd6cSJohn Marino yyerror (char *msg)
1618*ef5ccd6cSJohn Marino {
1619*ef5ccd6cSJohn Marino   if (prev_lexptr)
1620*ef5ccd6cSJohn Marino     lexptr = prev_lexptr;
1621*ef5ccd6cSJohn Marino 
1622*ef5ccd6cSJohn Marino   error (_("A %s in expression, near `%s'."), (msg ? msg : "error"), lexptr);
1623*ef5ccd6cSJohn Marino }
1624