]> Git Repo - binutils.git/blob - gdb/c-exp.y
ansi name abuse changes
[binutils.git] / gdb / c-exp.y
1 /* YACC parser for C expressions, for GDB.
2    Copyright (C) 1986, 1989, 1990, 1991 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 2 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, write to the Free Software
18 Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.  */
19
20 /* Parse a C expression from text in a string,
21    and return the result as a  struct expression  pointer.
22    That structure contains arithmetic operations in reverse polish,
23    with constants represented by operations that are followed by special data.
24    See expression.h for the details of the format.
25    What is important here is that it can be built up sequentially
26    during the process of parsing; the lower levels of the tree always
27    come first in the result.  */
28    
29 %{
30
31 #include <stdio.h>
32 #include <string.h>
33 #include "defs.h"
34 #include "param.h"
35 #include "symtab.h"
36 #include "frame.h"
37 #include "expression.h"
38 #include "parser-defs.h"
39 #include "value.h"
40 #include "language.h"
41
42 /* These MUST be included in any grammar file!!!! 
43    Please choose unique names! */
44 #define yyparse c_parse
45 #define yylex   c_lex
46 #define yyerror c_error
47 #define yylval  c_lval
48 #define yychar  c_char
49 #define yydebug c_debug
50 #define yypact  c_pact  
51 #define yyr1    c_r1                    
52 #define yyr2    c_r2                    
53 #define yydef   c_def           
54 #define yychk   c_chk           
55 #define yypgo   c_pgo           
56 #define yyact   c_act           
57 #define yyexca  c_exca
58 #define yyerrflag c_errflag
59 #define yynerrs c_nerrs
60 #define yyps    c_ps
61 #define yypv    c_pv
62 #define yys     c_s
63 #define yystate c_state
64 #define yytmp   c_tmp
65 #define yyv     c_v
66 #define yyval   c_val
67 #define yylloc  c_lloc
68
69 /* Forward decls */
70 void yyerror ();
71 static int parse_number ();
72 int yyparse ();
73
74 /* #define      YYDEBUG 1 */
75
76 %}
77
78 /* Although the yacc "value" of an expression is not used,
79    since the result is stored in the structure being created,
80    other node types do have values.  */
81
82 %union
83   {
84     LONGEST lval;
85     unsigned LONGEST ulval;
86     double dval;
87     struct symbol *sym;
88     struct type *tval;
89     struct stoken sval;
90     struct ttype tsym;
91     struct symtoken ssym;
92     int voidval;
93     struct block *bval;
94     enum exp_opcode opcode;
95     struct internalvar *ivar;
96
97     struct type **tvec;
98     int *ivec;
99   }
100
101 %type <voidval> exp exp1 type_exp start variable
102 %type <tval> type typebase
103 %type <tvec> nonempty_typelist
104 /* %type <bval> block */
105
106 /* Fancy type parsing.  */
107 %type <voidval> func_mod direct_abs_decl abs_decl
108 %type <tval> ptype
109 %type <lval> array_mod
110
111 %token <lval> INT CHAR
112 %token <ulval> UINT
113 %token <dval> FLOAT
114
115 /* Both NAME and TYPENAME tokens represent symbols in the input,
116    and both convey their data as strings.
117    But a TYPENAME is a string that happens to be defined as a typedef
118    or builtin type name (such as int or char)
119    and a NAME is any other symbol.
120    Contexts where this distinction is not important can use the
121    nonterminal "name", which matches either NAME or TYPENAME.  */
122
123 %token <sval> STRING
124 %token <ssym> NAME /* BLOCKNAME defined below to give it higher precedence. */
125 %token <tsym> TYPENAME
126 %type <sval> name
127 %type <ssym> name_not_typename
128 %type <tsym> typename
129
130 /* A NAME_OR_INT is a symbol which is not known in the symbol table,
131    but which would parse as a valid number in the current input radix.
132    E.g. "c" when input_radix==16.  Depending on the parse, it will be
133    turned into a name or into a number.  NAME_OR_UINT ditto.  */
134
135 %token <ssym> NAME_OR_INT NAME_OR_UINT
136
137 %token STRUCT UNION ENUM SIZEOF UNSIGNED COLONCOLON
138 %token TEMPLATE
139 %token ERROR
140
141 /* Special type cases, put in to allow the parser to distinguish different
142    legal basetypes.  */
143 %token SIGNED LONG SHORT INT_KEYWORD
144
145 %token <lval> LAST REGNAME
146
147 %token <ivar> VARIABLE
148
149 %token <opcode> ASSIGN_MODIFY
150
151 /* C++ */
152 %token THIS
153
154 %left ','
155 %left ABOVE_COMMA
156 %right '=' ASSIGN_MODIFY
157 %right '?'
158 %left OR
159 %left AND
160 %left '|'
161 %left '^'
162 %left '&'
163 %left EQUAL NOTEQUAL
164 %left '<' '>' LEQ GEQ
165 %left LSH RSH
166 %left '@'
167 %left '+' '-'
168 %left '*' '/' '%'
169 %right UNARY INCREMENT DECREMENT
170 %right ARROW '.' '[' '('
171 %token <ssym> BLOCKNAME 
172 %type <bval> block
173 %left COLONCOLON
174 \f
175 %%
176
177 start   :       exp1
178         |       type_exp
179         ;
180
181 type_exp:       type
182                         { write_exp_elt_opcode(OP_TYPE);
183                           write_exp_elt_type($1);
184                           write_exp_elt_opcode(OP_TYPE);}
185         ;
186
187 /* Expressions, including the comma operator.  */
188 exp1    :       exp
189         |       exp1 ',' exp
190                         { write_exp_elt_opcode (BINOP_COMMA); }
191         ;
192
193 /* Expressions, not including the comma operator.  */
194 exp     :       '*' exp    %prec UNARY
195                         { write_exp_elt_opcode (UNOP_IND); }
196
197 exp     :       '&' exp    %prec UNARY
198                         { write_exp_elt_opcode (UNOP_ADDR); }
199
200 exp     :       '-' exp    %prec UNARY
201                         { write_exp_elt_opcode (UNOP_NEG); }
202         ;
203
204 exp     :       '!' exp    %prec UNARY
205                         { write_exp_elt_opcode (UNOP_ZEROP); }
206         ;
207
208 exp     :       '~' exp    %prec UNARY
209                         { write_exp_elt_opcode (UNOP_LOGNOT); }
210         ;
211
212 exp     :       INCREMENT exp    %prec UNARY
213                         { write_exp_elt_opcode (UNOP_PREINCREMENT); }
214         ;
215
216 exp     :       DECREMENT exp    %prec UNARY
217                         { write_exp_elt_opcode (UNOP_PREDECREMENT); }
218         ;
219
220 exp     :       exp INCREMENT    %prec UNARY
221                         { write_exp_elt_opcode (UNOP_POSTINCREMENT); }
222         ;
223
224 exp     :       exp DECREMENT    %prec UNARY
225                         { write_exp_elt_opcode (UNOP_POSTDECREMENT); }
226         ;
227
228 exp     :       SIZEOF exp       %prec UNARY
229                         { write_exp_elt_opcode (UNOP_SIZEOF); }
230         ;
231
232 exp     :       exp ARROW name
233                         { write_exp_elt_opcode (STRUCTOP_PTR);
234                           write_exp_string ($3);
235                           write_exp_elt_opcode (STRUCTOP_PTR); }
236         ;
237
238 exp     :       exp ARROW '*' exp
239                         { write_exp_elt_opcode (STRUCTOP_MPTR); }
240         ;
241
242 exp     :       exp '.' name
243                         { write_exp_elt_opcode (STRUCTOP_STRUCT);
244                           write_exp_string ($3);
245                           write_exp_elt_opcode (STRUCTOP_STRUCT); }
246         ;
247
248 exp     :       exp '.' '*' exp
249                         { write_exp_elt_opcode (STRUCTOP_MEMBER); }
250         ;
251
252 exp     :       exp '[' exp1 ']'
253                         { write_exp_elt_opcode (BINOP_SUBSCRIPT); }
254         ;
255
256 exp     :       exp '(' 
257                         /* This is to save the value of arglist_len
258                            being accumulated by an outer function call.  */
259                         { start_arglist (); }
260                 arglist ')'     %prec ARROW
261                         { write_exp_elt_opcode (OP_FUNCALL);
262                           write_exp_elt_longcst ((LONGEST) end_arglist ());
263                           write_exp_elt_opcode (OP_FUNCALL); }
264         ;
265
266 arglist :
267         ;
268
269 arglist :       exp
270                         { arglist_len = 1; }
271         ;
272
273 arglist :       arglist ',' exp   %prec ABOVE_COMMA
274                         { arglist_len++; }
275         ;
276
277 exp     :       '{' type '}' exp  %prec UNARY
278                         { write_exp_elt_opcode (UNOP_MEMVAL);
279                           write_exp_elt_type ($2);
280                           write_exp_elt_opcode (UNOP_MEMVAL); }
281         ;
282
283 exp     :       '(' type ')' exp  %prec UNARY
284                         { write_exp_elt_opcode (UNOP_CAST);
285                           write_exp_elt_type ($2);
286                           write_exp_elt_opcode (UNOP_CAST); }
287         ;
288
289 exp     :       '(' exp1 ')'
290                         { }
291         ;
292
293 /* Binary operators in order of decreasing precedence.  */
294
295 exp     :       exp '@' exp
296                         { write_exp_elt_opcode (BINOP_REPEAT); }
297         ;
298
299 exp     :       exp '*' exp
300                         { write_exp_elt_opcode (BINOP_MUL); }
301         ;
302
303 exp     :       exp '/' exp
304                         { write_exp_elt_opcode (BINOP_DIV); }
305         ;
306
307 exp     :       exp '%' exp
308                         { write_exp_elt_opcode (BINOP_REM); }
309         ;
310
311 exp     :       exp '+' exp
312                         { write_exp_elt_opcode (BINOP_ADD); }
313         ;
314
315 exp     :       exp '-' exp
316                         { write_exp_elt_opcode (BINOP_SUB); }
317         ;
318
319 exp     :       exp LSH exp
320                         { write_exp_elt_opcode (BINOP_LSH); }
321         ;
322
323 exp     :       exp RSH exp
324                         { write_exp_elt_opcode (BINOP_RSH); }
325         ;
326
327 exp     :       exp EQUAL exp
328                         { write_exp_elt_opcode (BINOP_EQUAL); }
329         ;
330
331 exp     :       exp NOTEQUAL exp
332                         { write_exp_elt_opcode (BINOP_NOTEQUAL); }
333         ;
334
335 exp     :       exp LEQ exp
336                         { write_exp_elt_opcode (BINOP_LEQ); }
337         ;
338
339 exp     :       exp GEQ exp
340                         { write_exp_elt_opcode (BINOP_GEQ); }
341         ;
342
343 exp     :       exp '<' exp
344                         { write_exp_elt_opcode (BINOP_LESS); }
345         ;
346
347 exp     :       exp '>' exp
348                         { write_exp_elt_opcode (BINOP_GTR); }
349         ;
350
351 exp     :       exp '&' exp
352                         { write_exp_elt_opcode (BINOP_LOGAND); }
353         ;
354
355 exp     :       exp '^' exp
356                         { write_exp_elt_opcode (BINOP_LOGXOR); }
357         ;
358
359 exp     :       exp '|' exp
360                         { write_exp_elt_opcode (BINOP_LOGIOR); }
361         ;
362
363 exp     :       exp AND exp
364                         { write_exp_elt_opcode (BINOP_AND); }
365         ;
366
367 exp     :       exp OR exp
368                         { write_exp_elt_opcode (BINOP_OR); }
369         ;
370
371 exp     :       exp '?' exp ':' exp     %prec '?'
372                         { write_exp_elt_opcode (TERNOP_COND); }
373         ;
374                           
375 exp     :       exp '=' exp
376                         { write_exp_elt_opcode (BINOP_ASSIGN); }
377         ;
378
379 exp     :       exp ASSIGN_MODIFY exp
380                         { write_exp_elt_opcode (BINOP_ASSIGN_MODIFY);
381                           write_exp_elt_opcode ($2);
382                           write_exp_elt_opcode (BINOP_ASSIGN_MODIFY); }
383         ;
384
385 exp     :       INT
386                         { write_exp_elt_opcode (OP_LONG);
387                           if ($1 == (int) $1 || $1 == (unsigned int) $1)
388                             write_exp_elt_type (builtin_type_int);
389                           else
390                             write_exp_elt_type (BUILTIN_TYPE_LONGEST);
391                           write_exp_elt_longcst ((LONGEST) $1);
392                           write_exp_elt_opcode (OP_LONG); }
393         ;
394
395 exp     :       NAME_OR_INT
396                         { YYSTYPE val;
397                           parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
398                           write_exp_elt_opcode (OP_LONG);
399                           if (val.lval == (int) val.lval ||
400                               val.lval == (unsigned int) val.lval)
401                             write_exp_elt_type (builtin_type_int);
402                           else
403                             write_exp_elt_type (BUILTIN_TYPE_LONGEST);
404                           write_exp_elt_longcst (val.lval);
405                           write_exp_elt_opcode (OP_LONG); }
406         ;
407
408 exp     :       UINT
409                         {
410                           write_exp_elt_opcode (OP_LONG);
411                           if ($1 == (unsigned int) $1)
412                             write_exp_elt_type (builtin_type_unsigned_int);
413                           else
414                             write_exp_elt_type (BUILTIN_TYPE_UNSIGNED_LONGEST);
415                           write_exp_elt_longcst ((LONGEST) $1);
416                           write_exp_elt_opcode (OP_LONG);
417                         }
418         ;
419
420 exp     :       NAME_OR_UINT
421                         { YYSTYPE val;
422                           parse_number ($1.stoken.ptr, $1.stoken.length, 0, &val);
423                           write_exp_elt_opcode (OP_LONG);
424                           if (val.ulval == (unsigned int) val.ulval)
425                             write_exp_elt_type (builtin_type_unsigned_int);
426                           else
427                             write_exp_elt_type (BUILTIN_TYPE_UNSIGNED_LONGEST);
428                           write_exp_elt_longcst ((LONGEST)val.ulval);
429                           write_exp_elt_opcode (OP_LONG);
430                         }
431         ;
432
433 exp     :       CHAR
434                         { write_exp_elt_opcode (OP_LONG);
435                           write_exp_elt_type (builtin_type_char);
436                           write_exp_elt_longcst ((LONGEST) $1);
437                           write_exp_elt_opcode (OP_LONG); }
438         ;
439
440 exp     :       FLOAT
441                         { write_exp_elt_opcode (OP_DOUBLE);
442                           write_exp_elt_type (builtin_type_double);
443                           write_exp_elt_dblcst ($1);
444                           write_exp_elt_opcode (OP_DOUBLE); }
445         ;
446
447 exp     :       variable
448         ;
449
450 exp     :       LAST
451                         { write_exp_elt_opcode (OP_LAST);
452                           write_exp_elt_longcst ((LONGEST) $1);
453                           write_exp_elt_opcode (OP_LAST); }
454         ;
455
456 exp     :       REGNAME
457                         { write_exp_elt_opcode (OP_REGISTER);
458                           write_exp_elt_longcst ((LONGEST) $1);
459                           write_exp_elt_opcode (OP_REGISTER); }
460         ;
461
462 exp     :       VARIABLE
463                         { write_exp_elt_opcode (OP_INTERNALVAR);
464                           write_exp_elt_intern ($1);
465                           write_exp_elt_opcode (OP_INTERNALVAR); }
466         ;
467
468 exp     :       SIZEOF '(' type ')'     %prec UNARY
469                         { write_exp_elt_opcode (OP_LONG);
470                           write_exp_elt_type (builtin_type_int);
471                           write_exp_elt_longcst ((LONGEST) TYPE_LENGTH ($3));
472                           write_exp_elt_opcode (OP_LONG); }
473         ;
474
475 exp     :       STRING
476                         { write_exp_elt_opcode (OP_STRING);
477                           write_exp_string ($1);
478                           write_exp_elt_opcode (OP_STRING); }
479         ;
480
481 /* C++.  */
482 exp     :       THIS
483                         { write_exp_elt_opcode (OP_THIS);
484                           write_exp_elt_opcode (OP_THIS); }
485         ;
486
487 /* end of C++.  */
488
489 block   :       BLOCKNAME
490                         {
491                           if ($1.sym != 0)
492                               $$ = SYMBOL_BLOCK_VALUE ($1.sym);
493                           else
494                             {
495                               struct symtab *tem =
496                                   lookup_symtab (copy_name ($1.stoken));
497                               if (tem)
498                                 $$ = BLOCKVECTOR_BLOCK
499                                          (BLOCKVECTOR (tem), STATIC_BLOCK);
500                               else
501                                 error ("No file or function \"%s\".",
502                                        copy_name ($1.stoken));
503                             }
504                         }
505         ;
506
507 block   :       block COLONCOLON name
508                         { struct symbol *tem
509                             = lookup_symbol (copy_name ($3), $1,
510                                              VAR_NAMESPACE, 0, NULL);
511                           if (!tem || SYMBOL_CLASS (tem) != LOC_BLOCK)
512                             error ("No function \"%s\" in specified context.",
513                                    copy_name ($3));
514                           $$ = SYMBOL_BLOCK_VALUE (tem); }
515         ;
516
517 variable:       block COLONCOLON name
518                         { struct symbol *sym;
519                           sym = lookup_symbol (copy_name ($3), $1,
520                                                VAR_NAMESPACE, 0, NULL);
521                           if (sym == 0)
522                             error ("No symbol \"%s\" in specified context.",
523                                    copy_name ($3));
524
525                           write_exp_elt_opcode (OP_VAR_VALUE);
526                           write_exp_elt_sym (sym);
527                           write_exp_elt_opcode (OP_VAR_VALUE); }
528         ;
529
530 variable:       typebase COLONCOLON name
531                         {
532                           struct type *type = $1;
533                           if (TYPE_CODE (type) != TYPE_CODE_STRUCT
534                               && TYPE_CODE (type) != TYPE_CODE_UNION)
535                             error ("`%s' is not defined as an aggregate type.",
536                                    TYPE_NAME (type));
537
538                           write_exp_elt_opcode (OP_SCOPE);
539                           write_exp_elt_type (type);
540                           write_exp_string ($3);
541                           write_exp_elt_opcode (OP_SCOPE);
542                         }
543         |       typebase COLONCOLON '~' name
544                         {
545                           struct type *type = $1;
546                           if (TYPE_CODE (type) != TYPE_CODE_STRUCT
547                               && TYPE_CODE (type) != TYPE_CODE_UNION)
548                             error ("`%s' is not defined as an aggregate type.",
549                                    TYPE_NAME (type));
550
551                           if (strcmp (type_name_no_tag (type), $4.ptr))
552                             error ("invalid destructor `%s::~%s'",
553                                    type_name_no_tag (type), $4.ptr);
554
555                           write_exp_elt_opcode (OP_SCOPE);
556                           write_exp_elt_type (type);
557                           write_exp_string ($4);
558                           write_exp_elt_opcode (OP_SCOPE);
559                           write_exp_elt_opcode (UNOP_LOGNOT);
560                         }
561         |       COLONCOLON name
562                         {
563                           char *name = copy_name ($2);
564                           struct symbol *sym;
565                           int i;
566
567                           sym =
568                             lookup_symbol (name, 0, VAR_NAMESPACE, 0, NULL);
569                           if (sym)
570                             {
571                               write_exp_elt_opcode (OP_VAR_VALUE);
572                               write_exp_elt_sym (sym);
573                               write_exp_elt_opcode (OP_VAR_VALUE);
574                               break;
575                             }
576                           for (i = 0; i < misc_function_count; i++)
577                             if (!strcmp (misc_function_vector[i].name, name))
578                               break;
579
580                           if (i < misc_function_count)
581                             {
582                               enum misc_function_type mft =
583                                   misc_function_vector[i].type;
584                               
585                               write_exp_elt_opcode (OP_LONG);
586                               write_exp_elt_type (builtin_type_int);
587                               write_exp_elt_longcst ((LONGEST) misc_function_vector[i].address);
588                               write_exp_elt_opcode (OP_LONG);
589                               write_exp_elt_opcode (UNOP_MEMVAL);
590                               if (mft == mf_data || mft == mf_bss)
591                                 write_exp_elt_type (builtin_type_int);
592                               else if (mft == mf_text)
593                                 write_exp_elt_type (lookup_function_type (builtin_type_int));
594                               else
595                                 write_exp_elt_type (builtin_type_char);
596                               write_exp_elt_opcode (UNOP_MEMVAL);
597                             }
598                           else
599                             if (symtab_list == 0
600                                 && partial_symtab_list == 0)
601                               error ("No symbol table is loaded.  Use the \"file\" command.");
602                             else
603                               error ("No symbol \"%s\" in current context.", name);
604                         }
605         ;
606
607 variable:       name_not_typename
608                         { struct symbol *sym = $1.sym;
609
610                           if (sym)
611                             {
612                               switch (SYMBOL_CLASS (sym))
613                                 {
614                                 case LOC_REGISTER:
615                                 case LOC_ARG:
616                                 case LOC_REF_ARG:
617                                 case LOC_REGPARM:
618                                 case LOC_LOCAL:
619                                 case LOC_LOCAL_ARG:
620                                   if (innermost_block == 0 ||
621                                       contained_in (block_found, 
622                                                     innermost_block))
623                                     innermost_block = block_found;
624                                 case LOC_UNDEF:
625                                 case LOC_CONST:
626                                 case LOC_STATIC:
627                                 case LOC_TYPEDEF:
628                                 case LOC_LABEL:
629                                 case LOC_BLOCK:
630                                 case LOC_CONST_BYTES:
631
632                                   /* In this case the expression can
633                                      be evaluated regardless of what
634                                      frame we are in, so there is no
635                                      need to check for the
636                                      innermost_block.  These cases are
637                                      listed so that gcc -Wall will
638                                      report types that may not have
639                                      been considered.  */
640
641                                   break;
642                                 }
643                               write_exp_elt_opcode (OP_VAR_VALUE);
644                               write_exp_elt_sym (sym);
645                               write_exp_elt_opcode (OP_VAR_VALUE);
646                             }
647                           else if ($1.is_a_field_of_this)
648                             {
649                               /* C++: it hangs off of `this'.  Must
650                                  not inadvertently convert from a method call
651                                  to data ref.  */
652                               if (innermost_block == 0 || 
653                                   contained_in (block_found, innermost_block))
654                                 innermost_block = block_found;
655                               write_exp_elt_opcode (OP_THIS);
656                               write_exp_elt_opcode (OP_THIS);
657                               write_exp_elt_opcode (STRUCTOP_PTR);
658                               write_exp_string ($1.stoken);
659                               write_exp_elt_opcode (STRUCTOP_PTR);
660                             }
661                           else
662                             {
663                               register int i;
664                               register char *arg = copy_name ($1.stoken);
665
666                                 /* FIXME, this search is linear!  At least
667                                    optimize the strcmp with a 1-char cmp... */
668                               for (i = 0; i < misc_function_count; i++)
669                                 if (!strcmp (misc_function_vector[i].name, arg))
670                                   break;
671
672                               if (i < misc_function_count)
673                                 {
674                                   enum misc_function_type mft =
675                                       misc_function_vector[i].type;
676                                   
677                                   write_exp_elt_opcode (OP_LONG);
678                                   write_exp_elt_type (builtin_type_int);
679                                   write_exp_elt_longcst ((LONGEST) misc_function_vector[i].address);
680                                   write_exp_elt_opcode (OP_LONG);
681                                   write_exp_elt_opcode (UNOP_MEMVAL);
682                                   if (mft == mf_data || mft == mf_bss)
683                                     write_exp_elt_type (builtin_type_int);
684                                   else if (mft == mf_text)
685                                     write_exp_elt_type (lookup_function_type (builtin_type_int));
686                                   else
687                                     write_exp_elt_type (builtin_type_char);
688                                   write_exp_elt_opcode (UNOP_MEMVAL);
689                                 }
690                               else if (symtab_list == 0
691                                        && partial_symtab_list == 0)
692                                 error ("No symbol table is loaded.  Use the \"file\" command.");
693                               else
694                                 error ("No symbol \"%s\" in current context.",
695                                        copy_name ($1.stoken));
696                             }
697                         }
698         ;
699
700
701 ptype   :       typebase
702         |       typebase abs_decl
703                 {
704                   /* This is where the interesting stuff happens.  */
705                   int done = 0;
706                   int array_size;
707                   struct type *follow_type = $1;
708                   
709                   while (!done)
710                     switch (pop_type ())
711                       {
712                       case tp_end:
713                         done = 1;
714                         break;
715                       case tp_pointer:
716                         follow_type = lookup_pointer_type (follow_type);
717                         break;
718                       case tp_reference:
719                         follow_type = lookup_reference_type (follow_type);
720                         break;
721                       case tp_array:
722                         array_size = pop_type_int ();
723                         if (array_size != -1)
724                           follow_type = create_array_type (follow_type,
725                                                            array_size);
726                         else
727                           follow_type = lookup_pointer_type (follow_type);
728                         break;
729                       case tp_function:
730                         follow_type = lookup_function_type (follow_type);
731                         break;
732                       }
733                   $$ = follow_type;
734                 }
735         ;
736
737 abs_decl:       '*'
738                         { push_type (tp_pointer); $$ = 0; }
739         |       '*' abs_decl
740                         { push_type (tp_pointer); $$ = $2; }
741         |       '&'
742                         { push_type (tp_reference); $$ = 0; }
743         |       '&' abs_decl
744                         { push_type (tp_reference); $$ = $2; }
745         |       direct_abs_decl
746         ;
747
748 direct_abs_decl: '(' abs_decl ')'
749                         { $$ = $2; }
750         |       direct_abs_decl array_mod
751                         {
752                           push_type_int ($2);
753                           push_type (tp_array);
754                         }
755         |       array_mod
756                         {
757                           push_type_int ($1);
758                           push_type (tp_array);
759                           $$ = 0;
760                         }
761         |       direct_abs_decl func_mod
762                         { push_type (tp_function); }
763         |       func_mod
764                         { push_type (tp_function); }
765         ;
766
767 array_mod:      '[' ']'
768                         { $$ = -1; }
769         |       '[' INT ']'
770                         { $$ = $2; }
771         ;
772
773 func_mod:       '(' ')'
774                         { $$ = 0; }
775         |       '(' nonempty_typelist ')'
776                         { free ($2); $$ = 0; }
777         ;
778
779 type    :       ptype
780         |       typebase COLONCOLON '*'
781                         { $$ = lookup_member_type (builtin_type_int, $1); }
782         |       type '(' typebase COLONCOLON '*' ')'
783                         { $$ = lookup_member_type ($1, $3); }
784         |       type '(' typebase COLONCOLON '*' ')' '(' ')'
785                         { $$ = lookup_member_type
786                             (lookup_function_type ($1), $3); }
787         |       type '(' typebase COLONCOLON '*' ')' '(' nonempty_typelist ')'
788                         { $$ = lookup_member_type
789                             (lookup_function_type ($1), $3);
790                           free ($8); }
791         ;
792
793 typebase
794         :       TYPENAME
795                         { $$ = $1.type; }
796         |       INT_KEYWORD
797                         { $$ = builtin_type_int; }
798         |       LONG
799                         { $$ = builtin_type_long; }
800         |       SHORT
801                         { $$ = builtin_type_short; }
802         |       LONG INT_KEYWORD
803                         { $$ = builtin_type_long; }
804         |       UNSIGNED LONG INT_KEYWORD
805                         { $$ = builtin_type_unsigned_long; }
806         |       LONG LONG
807                         { $$ = builtin_type_long_long; }
808         |       LONG LONG INT_KEYWORD
809                         { $$ = builtin_type_long_long; }
810         |       UNSIGNED LONG LONG
811                         { $$ = builtin_type_unsigned_long_long; }
812         |       UNSIGNED LONG LONG INT_KEYWORD
813                         { $$ = builtin_type_unsigned_long_long; }
814         |       SHORT INT_KEYWORD
815                         { $$ = builtin_type_short; }
816         |       UNSIGNED SHORT INT_KEYWORD
817                         { $$ = builtin_type_unsigned_short; }
818         |       STRUCT name
819                         { $$ = lookup_struct (copy_name ($2),
820                                               expression_context_block); }
821         |       UNION name
822                         { $$ = lookup_union (copy_name ($2),
823                                              expression_context_block); }
824         |       ENUM name
825                         { $$ = lookup_enum (copy_name ($2),
826                                             expression_context_block); }
827         |       UNSIGNED typename
828                         { $$ = lookup_unsigned_typename (TYPE_NAME($2.type)); }
829         |       UNSIGNED
830                         { $$ = builtin_type_unsigned_int; }
831         |       SIGNED typename
832                         { $$ = $2.type; }
833         |       SIGNED
834                         { $$ = builtin_type_int; }
835         |       TEMPLATE name '<' type '>'
836                         { $$ = lookup_template_type(copy_name($2), $4,
837                                                     expression_context_block);
838                         }
839         ;
840
841 typename:       TYPENAME
842         |       INT_KEYWORD
843                 {
844                   $$.stoken.ptr = "int";
845                   $$.stoken.length = 3;
846                   $$.type = builtin_type_int;
847                 }
848         |       LONG
849                 {
850                   $$.stoken.ptr = "long";
851                   $$.stoken.length = 4;
852                   $$.type = builtin_type_long;
853                 }
854         |       SHORT
855                 {
856                   $$.stoken.ptr = "short";
857                   $$.stoken.length = 5;
858                   $$.type = builtin_type_short;
859                 }
860         ;
861
862 nonempty_typelist
863         :       type
864                 { $$ = (struct type **)xmalloc (sizeof (struct type *) * 2);
865                   $$[0] = (struct type *)0;
866                   $$[1] = $1;
867                 }
868         |       nonempty_typelist ',' type
869                 { int len = sizeof (struct type *) * ++($<ivec>1[0]);
870                   $$ = (struct type **)xrealloc ($1, len);
871                   $$[$<ivec>$[0]] = $3;
872                 }
873         ;
874
875 name    :       NAME { $$ = $1.stoken; }
876         |       BLOCKNAME { $$ = $1.stoken; }
877         |       TYPENAME { $$ = $1.stoken; }
878         |       NAME_OR_INT  { $$ = $1.stoken; }
879         |       NAME_OR_UINT  { $$ = $1.stoken; }
880         ;
881
882 name_not_typename :     NAME
883         |       BLOCKNAME
884 /* These would be useful if name_not_typename was useful, but it is just
885    a fake for "variable", so these cause reduce/reduce conflicts because
886    the parser can't tell whether NAME_OR_INT is a name_not_typename (=variable,
887    =exp) or just an exp.  If name_not_typename was ever used in an lvalue
888    context where only a name could occur, this might be useful.
889         |       NAME_OR_INT
890         |       NAME_OR_UINT
891  */
892         ;
893
894 %%
895
896 /* Take care of parsing a number (anything that starts with a digit).
897    Set yylval and return the token type; update lexptr.
898    LEN is the number of characters in it.  */
899
900 /*** Needs some error checking for the float case ***/
901
902 static int
903 parse_number (p, len, parsed_float, putithere)
904      register char *p;
905      register int len;
906      int parsed_float;
907      YYSTYPE *putithere;
908 {
909   register LONGEST n = 0;
910   register LONGEST prevn = 0;
911   register int i;
912   register int c;
913   register int base = input_radix;
914   int unsigned_p = 0;
915
916   extern double atof ();
917
918   if (parsed_float)
919     {
920       /* It's a float since it contains a point or an exponent.  */
921       putithere->dval = atof (p);
922       return FLOAT;
923     }
924
925   /* Handle base-switching prefixes 0x, 0t, 0d, 0 */
926   if (p[0] == '0')
927     switch (p[1])
928       {
929       case 'x':
930       case 'X':
931         if (len >= 3)
932           {
933             p += 2;
934             base = 16;
935             len -= 2;
936           }
937         break;
938
939       case 't':
940       case 'T':
941       case 'd':
942       case 'D':
943         if (len >= 3)
944           {
945             p += 2;
946             base = 10;
947             len -= 2;
948           }
949         break;
950
951       default:
952         base = 8;
953         break;
954       }
955
956   while (len-- > 0)
957     {
958       c = *p++;
959       if (c >= 'A' && c <= 'Z')
960         c += 'a' - 'A';
961       if (c != 'l' && c != 'u')
962         n *= base;
963       if (c >= '0' && c <= '9')
964         n += i = c - '0';
965       else
966         {
967           if (base > 10 && c >= 'a' && c <= 'f')
968             n += i = c - 'a' + 10;
969           else if (len == 0 && c == 'l')
970             ;
971           else if (len == 0 && c == 'u')
972             unsigned_p = 1;
973           else
974             return ERROR;       /* Char not a digit */
975         }
976       if (i >= base)
977         return ERROR;           /* Invalid digit in this base */
978       if(!unsigned_p && (prevn >= n))
979          unsigned_p=1;          /* Try something unsigned */
980       /* Don't do the range check if n==i and i==0, since that special
981          case will give an overflow error. */
982       if(RANGE_CHECK && n!=0)
983       { 
984          if((unsigned_p && (unsigned)prevn >= (unsigned)n))
985             range_error("Overflow on numeric constant.");        
986       }
987       prevn=n;
988     }
989
990   if (unsigned_p)
991     {
992       putithere->ulval = n;
993       return UINT;
994     }
995   else
996     {
997       putithere->lval = n;
998       return INT;
999     }
1000 }
1001
1002 struct token
1003 {
1004   char *operator;
1005   int token;
1006   enum exp_opcode opcode;
1007 };
1008
1009 const static struct token tokentab3[] =
1010   {
1011     {">>=", ASSIGN_MODIFY, BINOP_RSH},
1012     {"<<=", ASSIGN_MODIFY, BINOP_LSH}
1013   };
1014
1015 const static struct token tokentab2[] =
1016   {
1017     {"+=", ASSIGN_MODIFY, BINOP_ADD},
1018     {"-=", ASSIGN_MODIFY, BINOP_SUB},
1019     {"*=", ASSIGN_MODIFY, BINOP_MUL},
1020     {"/=", ASSIGN_MODIFY, BINOP_DIV},
1021     {"%=", ASSIGN_MODIFY, BINOP_REM},
1022     {"|=", ASSIGN_MODIFY, BINOP_LOGIOR},
1023     {"&=", ASSIGN_MODIFY, BINOP_LOGAND},
1024     {"^=", ASSIGN_MODIFY, BINOP_LOGXOR},
1025     {"++", INCREMENT, BINOP_END},
1026     {"--", DECREMENT, BINOP_END},
1027     {"->", ARROW, BINOP_END},
1028     {"&&", AND, BINOP_END},
1029     {"||", OR, BINOP_END},
1030     {"::", COLONCOLON, BINOP_END},
1031     {"<<", LSH, BINOP_END},
1032     {">>", RSH, BINOP_END},
1033     {"==", EQUAL, BINOP_END},
1034     {"!=", NOTEQUAL, BINOP_END},
1035     {"<=", LEQ, BINOP_END},
1036     {">=", GEQ, BINOP_END}
1037   };
1038
1039 /* Read one token, getting characters through lexptr.  */
1040
1041 int
1042 yylex ()
1043 {
1044   register int c;
1045   register int namelen;
1046   register unsigned i;
1047   register char *tokstart;
1048
1049  retry:
1050
1051   tokstart = lexptr;
1052   /* See if it is a special token of length 3.  */
1053   for (i = 0; i < sizeof tokentab3 / sizeof tokentab3[0]; i++)
1054     if (!strncmp (tokstart, tokentab3[i].operator, 3))
1055       {
1056         lexptr += 3;
1057         yylval.opcode = tokentab3[i].opcode;
1058         return tokentab3[i].token;
1059       }
1060
1061   /* See if it is a special token of length 2.  */
1062   for (i = 0; i < sizeof tokentab2 / sizeof tokentab2[0]; i++)
1063     if (!strncmp (tokstart, tokentab2[i].operator, 2))
1064       {
1065         lexptr += 2;
1066         yylval.opcode = tokentab2[i].opcode;
1067         return tokentab2[i].token;
1068       }
1069
1070   switch (c = *tokstart)
1071     {
1072     case 0:
1073       return 0;
1074
1075     case ' ':
1076     case '\t':
1077     case '\n':
1078       lexptr++;
1079       goto retry;
1080
1081     case '\'':
1082       lexptr++;
1083       c = *lexptr++;
1084       if (c == '\\')
1085         c = parse_escape (&lexptr);
1086       yylval.lval = c;
1087       c = *lexptr++;
1088       if (c != '\'')
1089         error ("Invalid character constant.");
1090       return CHAR;
1091
1092     case '(':
1093       paren_depth++;
1094       lexptr++;
1095       return c;
1096
1097     case ')':
1098       if (paren_depth == 0)
1099         return 0;
1100       paren_depth--;
1101       lexptr++;
1102       return c;
1103
1104     case ',':
1105       if (comma_terminates && paren_depth == 0)
1106         return 0;
1107       lexptr++;
1108       return c;
1109
1110     case '.':
1111       /* Might be a floating point number.  */
1112       if (lexptr[1] < '0' || lexptr[1] > '9')
1113         goto symbol;            /* Nope, must be a symbol. */
1114       /* FALL THRU into number case.  */
1115
1116     case '0':
1117     case '1':
1118     case '2':
1119     case '3':
1120     case '4':
1121     case '5':
1122     case '6':
1123     case '7':
1124     case '8':
1125     case '9':
1126       {
1127         /* It's a number.  */
1128         int got_dot = 0, got_e = 0, toktype;
1129         register char *p = tokstart;
1130         int hex = input_radix > 10;
1131
1132         if (c == '0' && (p[1] == 'x' || p[1] == 'X'))
1133           {
1134             p += 2;
1135             hex = 1;
1136           }
1137         else if (c == '0' && (p[1]=='t' || p[1]=='T' || p[1]=='d' || p[1]=='D'))
1138           {
1139             p += 2;
1140             hex = 0;
1141           }
1142
1143         for (;; ++p)
1144           {
1145             if (!hex && !got_e && (*p == 'e' || *p == 'E'))
1146               got_dot = got_e = 1;
1147             else if (!hex && !got_dot && *p == '.')
1148               got_dot = 1;
1149             else if (got_e && (p[-1] == 'e' || p[-1] == 'E')
1150                      && (*p == '-' || *p == '+'))
1151               /* This is the sign of the exponent, not the end of the
1152                  number.  */
1153               continue;
1154             /* We will take any letters or digits.  parse_number will
1155                complain if past the radix, or if L or U are not final.  */
1156             else if ((*p < '0' || *p > '9')
1157                      && ((*p < 'a' || *p > 'z')
1158                                   && (*p < 'A' || *p > 'Z')))
1159               break;
1160           }
1161         toktype = parse_number (tokstart, p - tokstart, got_dot|got_e, &yylval);
1162         if (toktype == ERROR)
1163           {
1164             char *err_copy = (char *) alloca (p - tokstart + 1);
1165
1166             bcopy (tokstart, err_copy, p - tokstart);
1167             err_copy[p - tokstart] = 0;
1168             error ("Invalid number \"%s\".", err_copy);
1169           }
1170         lexptr = p;
1171         return toktype;
1172       }
1173
1174     case '+':
1175     case '-':
1176     case '*':
1177     case '/':
1178     case '%':
1179     case '|':
1180     case '&':
1181     case '^':
1182     case '~':
1183     case '!':
1184     case '@':
1185     case '<':
1186     case '>':
1187     case '[':
1188     case ']':
1189     case '?':
1190     case ':':
1191     case '=':
1192     case '{':
1193     case '}':
1194     symbol:
1195       lexptr++;
1196       return c;
1197
1198     case '"':
1199       for (namelen = 1; (c = tokstart[namelen]) != '"'; namelen++)
1200         if (c == '\\')
1201           {
1202             c = tokstart[++namelen];
1203             if (c >= '0' && c <= '9')
1204               {
1205                 c = tokstart[++namelen];
1206                 if (c >= '0' && c <= '9')
1207                   c = tokstart[++namelen];
1208               }
1209           }
1210       yylval.sval.ptr = tokstart + 1;
1211       yylval.sval.length = namelen - 1;
1212       lexptr += namelen + 1;
1213       return STRING;
1214     }
1215
1216   if (!(c == '_' || c == '$'
1217         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z')))
1218     /* We must have come across a bad character (e.g. ';').  */
1219     error ("Invalid character '%c' in expression.", c);
1220
1221   /* It's a name.  See how long it is.  */
1222   namelen = 0;
1223   for (c = tokstart[namelen];
1224        (c == '_' || c == '$' || (c >= '0' && c <= '9')
1225         || (c >= 'a' && c <= 'z') || (c >= 'A' && c <= 'Z'));
1226        c = tokstart[++namelen])
1227     ;
1228
1229   /* The token "if" terminates the expression and is NOT 
1230      removed from the input stream.  */
1231   if (namelen == 2 && tokstart[0] == 'i' && tokstart[1] == 'f')
1232     {
1233       return 0;
1234     }
1235
1236   lexptr += namelen;
1237
1238   /* Handle the tokens $digits; also $ (short for $0) and $$ (short for $$1)
1239      and $$digits (equivalent to $<-digits> if you could type that).
1240      Make token type LAST, and put the number (the digits) in yylval.  */
1241
1242   if (*tokstart == '$')
1243     {
1244       register int negate = 0;
1245       c = 1;
1246       /* Double dollar means negate the number and add -1 as well.
1247          Thus $$ alone means -1.  */
1248       if (namelen >= 2 && tokstart[1] == '$')
1249         {
1250           negate = 1;
1251           c = 2;
1252         }
1253       if (c == namelen)
1254         {
1255           /* Just dollars (one or two) */
1256           yylval.lval = - negate;
1257           return LAST;
1258         }
1259       /* Is the rest of the token digits?  */
1260       for (; c < namelen; c++)
1261         if (!(tokstart[c] >= '0' && tokstart[c] <= '9'))
1262           break;
1263       if (c == namelen)
1264         {
1265           yylval.lval = atoi (tokstart + 1 + negate);
1266           if (negate)
1267             yylval.lval = - yylval.lval;
1268           return LAST;
1269         }
1270     }
1271
1272   /* Handle tokens that refer to machine registers:
1273      $ followed by a register name.  */
1274
1275   if (*tokstart == '$') {
1276     for (c = 0; c < NUM_REGS; c++)
1277       if (namelen - 1 == strlen (reg_names[c])
1278           && !strncmp (tokstart + 1, reg_names[c], namelen - 1))
1279         {
1280           yylval.lval = c;
1281           return REGNAME;
1282         }
1283     for (c = 0; c < num_std_regs; c++)
1284      if (namelen - 1 == strlen (std_regs[c].name)
1285          && !strncmp (tokstart + 1, std_regs[c].name, namelen - 1))
1286        {
1287          yylval.lval = std_regs[c].regnum;
1288          return REGNAME;
1289        }
1290   }
1291   /* Catch specific keywords.  Should be done with a data structure.  */
1292   switch (namelen)
1293     {
1294     case 8:
1295       if (!strncmp (tokstart, "unsigned", 8))
1296         return UNSIGNED;
1297       if (!strncmp (tokstart, "template", 8))
1298         return TEMPLATE;
1299       break;
1300     case 6:
1301       if (!strncmp (tokstart, "struct", 6))
1302         return STRUCT;
1303       if (!strncmp (tokstart, "signed", 6))
1304         return SIGNED;
1305       if (!strncmp (tokstart, "sizeof", 6))      
1306         return SIZEOF;
1307       break;
1308     case 5:
1309       if (!strncmp (tokstart, "union", 5))
1310         return UNION;
1311       if (!strncmp (tokstart, "short", 5))
1312         return SHORT;
1313       break;
1314     case 4:
1315       if (!strncmp (tokstart, "enum", 4))
1316         return ENUM;
1317       if (!strncmp (tokstart, "long", 4))
1318         return LONG;
1319       if (!strncmp (tokstart, "this", 4))
1320         {
1321           static const char this_name[] =
1322                                  { CPLUS_MARKER, 't', 'h', 'i', 's', '\0' };
1323
1324           if (lookup_symbol (this_name, expression_context_block,
1325                              VAR_NAMESPACE, 0, NULL))
1326             return THIS;
1327         }
1328       break;
1329     case 3:
1330       if (!strncmp (tokstart, "int", 3))
1331         return INT_KEYWORD;
1332       break;
1333     default:
1334       break;
1335     }
1336
1337   yylval.sval.ptr = tokstart;
1338   yylval.sval.length = namelen;
1339
1340   /* Any other names starting in $ are debugger internal variables.  */
1341
1342   if (*tokstart == '$')
1343     {
1344       yylval.ivar =  lookup_internalvar (copy_name (yylval.sval) + 1);
1345       return VARIABLE;
1346     }
1347
1348   /* Use token-type BLOCKNAME for symbols that happen to be defined as
1349      functions or symtabs.  If this is not so, then ...
1350      Use token-type TYPENAME for symbols that happen to be defined
1351      currently as names of types; NAME for other symbols.
1352      The caller is not constrained to care about the distinction.  */
1353   {
1354     char *tmp = copy_name (yylval.sval);
1355     struct symbol *sym;
1356     int is_a_field_of_this = 0;
1357     int hextype;
1358
1359     sym = lookup_symbol (tmp, expression_context_block,
1360                          VAR_NAMESPACE,
1361                          current_language->la_language == language_cplus
1362                          ? &is_a_field_of_this : NULL,
1363                          NULL);
1364     if ((sym && SYMBOL_CLASS (sym) == LOC_BLOCK) ||
1365         lookup_partial_symtab (tmp))
1366       {
1367         yylval.ssym.sym = sym;
1368         yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1369         return BLOCKNAME;
1370       }
1371     if (sym && SYMBOL_CLASS (sym) == LOC_TYPEDEF)
1372         {
1373           yylval.tsym.type = SYMBOL_TYPE (sym);
1374           return TYPENAME;
1375         }
1376     if ((yylval.tsym.type = lookup_primitive_typename (tmp)) != 0)
1377         return TYPENAME;
1378
1379     /* Input names that aren't symbols but ARE valid hex numbers,
1380        when the input radix permits them, can be names or numbers
1381        depending on the parse.  Note we support radixes > 16 here.  */
1382     if (!sym && 
1383         ((tokstart[0] >= 'a' && tokstart[0] < 'a' + input_radix - 10) ||
1384          (tokstart[0] >= 'A' && tokstart[0] < 'A' + input_radix - 10)))
1385       {
1386         YYSTYPE newlval;        /* Its value is ignored.  */
1387         hextype = parse_number (tokstart, namelen, 0, &newlval);
1388         if (hextype == INT)
1389           {
1390             yylval.ssym.sym = sym;
1391             yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1392             return NAME_OR_INT;
1393           }
1394         if (hextype == UINT)
1395           {
1396             yylval.ssym.sym = sym;
1397             yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1398             return NAME_OR_UINT;
1399           }
1400       }
1401
1402     /* Any other kind of symbol */
1403     yylval.ssym.sym = sym;
1404     yylval.ssym.is_a_field_of_this = is_a_field_of_this;
1405     return NAME;
1406   }
1407 }
1408
1409 void
1410 yyerror (msg)
1411      char *msg;
1412 {
1413   error (error (msg ? msg : "Invalid syntax in expression.");
1414 }
1415 \f
1416 /* Table mapping opcodes into strings for printing operators
1417    and precedences of the operators.  */
1418
1419 const static struct op_print c_op_print_tab[] =
1420   {
1421     {",",  BINOP_COMMA, PREC_COMMA, 0},
1422     {"=",  BINOP_ASSIGN, PREC_ASSIGN, 1},
1423     {"||", BINOP_OR, PREC_OR, 0},
1424     {"&&", BINOP_AND, PREC_AND, 0},
1425     {"|",  BINOP_LOGIOR, PREC_LOGIOR, 0},
1426     {"&",  BINOP_LOGAND, PREC_LOGAND, 0},
1427     {"^",  BINOP_LOGXOR, PREC_LOGXOR, 0},
1428     {"==", BINOP_EQUAL, PREC_EQUAL, 0},
1429     {"!=", BINOP_NOTEQUAL, PREC_EQUAL, 0},
1430     {"<=", BINOP_LEQ, PREC_ORDER, 0},
1431     {">=", BINOP_GEQ, PREC_ORDER, 0},
1432     {">",  BINOP_GTR, PREC_ORDER, 0},
1433     {"<",  BINOP_LESS, PREC_ORDER, 0},
1434     {">>", BINOP_RSH, PREC_SHIFT, 0},
1435     {"<<", BINOP_LSH, PREC_SHIFT, 0},
1436     {"+",  BINOP_ADD, PREC_ADD, 0},
1437     {"-",  BINOP_SUB, PREC_ADD, 0},
1438     {"*",  BINOP_MUL, PREC_MUL, 0},
1439     {"/",  BINOP_DIV, PREC_MUL, 0},
1440     {"%",  BINOP_REM, PREC_MUL, 0},
1441     {"@",  BINOP_REPEAT, PREC_REPEAT, 0},
1442     {"-",  UNOP_NEG, PREC_PREFIX, 0},
1443     {"!",  UNOP_ZEROP, PREC_PREFIX, 0},
1444     {"~",  UNOP_LOGNOT, PREC_PREFIX, 0},
1445     {"*",  UNOP_IND, PREC_PREFIX, 0},
1446     {"&",  UNOP_ADDR, PREC_PREFIX, 0},
1447     {"sizeof ", UNOP_SIZEOF, PREC_PREFIX, 0},
1448     {"++", UNOP_PREINCREMENT, PREC_PREFIX, 0},
1449     {"--", UNOP_PREDECREMENT, PREC_PREFIX, 0},
1450     /* C++  */
1451     {"::", BINOP_SCOPE, PREC_PREFIX, 0},
1452 };
1453 \f
1454 /* These variables point to the objects
1455    representing the predefined C data types.  */
1456
1457 struct type *builtin_type_void;
1458 struct type *builtin_type_char;
1459 struct type *builtin_type_short;
1460 struct type *builtin_type_int;
1461 struct type *builtin_type_long;
1462 struct type *builtin_type_long_long;
1463 struct type *builtin_type_unsigned_char;
1464 struct type *builtin_type_unsigned_short;
1465 struct type *builtin_type_unsigned_int;
1466 struct type *builtin_type_unsigned_long;
1467 struct type *builtin_type_unsigned_long_long;
1468 struct type *builtin_type_float;
1469 struct type *builtin_type_double;
1470 struct type *builtin_type_long_double;
1471 struct type *builtin_type_complex;
1472 struct type *builtin_type_double_complex;
1473
1474 struct type ** const (c_builtin_types[]) = 
1475 {
1476   &builtin_type_int,
1477   &builtin_type_long,
1478   &builtin_type_short,
1479   &builtin_type_char,
1480   &builtin_type_float,
1481   &builtin_type_double,
1482   &builtin_type_void,
1483   &builtin_type_long_long,
1484   &builtin_type_unsigned_char,
1485   &builtin_type_unsigned_short,
1486   &builtin_type_unsigned_int,
1487   &builtin_type_unsigned_long,
1488   &builtin_type_unsigned_long_long,
1489   &builtin_type_long_double,
1490   &builtin_type_complex,
1491   &builtin_type_double_complex,
1492   0
1493 };
1494
1495 const struct language_defn c_language_defn = {
1496   "c",                          /* Language name */
1497   language_c,
1498   c_builtin_types,
1499   range_check_off,
1500   type_check_off,
1501   c_parse,
1502   c_error,
1503   &BUILTIN_TYPE_LONGEST,         /* longest signed   integral type */
1504   &BUILTIN_TYPE_UNSIGNED_LONGEST,/* longest unsigned integral type */
1505   &builtin_type_double,         /* longest floating point type */ /*FIXME*/
1506   "0x%x", "0x%", "x",           /* Hex   format, prefix, suffix */
1507   "0%o",  "0%",  "o",           /* Octal format, prefix, suffix */
1508   c_op_print_tab,               /* expression operators for printing */
1509   LANG_MAGIC
1510 };
1511
1512 const struct language_defn cplus_language_defn = {
1513   "c++",                                /* Language name */
1514   language_cplus,
1515   c_builtin_types,
1516   range_check_off,
1517   type_check_off,
1518   c_parse,
1519   c_error,
1520   &BUILTIN_TYPE_LONGEST,         /* longest signed   integral type */
1521   &BUILTIN_TYPE_UNSIGNED_LONGEST,/* longest unsigned integral type */
1522   &builtin_type_double,         /* longest floating point type */ /*FIXME*/
1523   "0x%x", "0x%", "x",           /* Hex   format, prefix, suffix */
1524   "0%o",  "0%",  "o",           /* Octal format, prefix, suffix */
1525   c_op_print_tab,               /* expression operators for printing */
1526   LANG_MAGIC
1527 };
1528
1529 void
1530 _initialize_c_exp ()
1531 {
1532   builtin_type_void =
1533     init_type (TYPE_CODE_VOID, 1, 0,
1534                "void");
1535   builtin_type_char =
1536     init_type (TYPE_CODE_INT, TARGET_CHAR_BIT / TARGET_CHAR_BIT, 0,
1537                "char");
1538   builtin_type_unsigned_char =
1539     init_type (TYPE_CODE_INT, TARGET_CHAR_BIT / TARGET_CHAR_BIT, 1,
1540                "unsigned char");
1541   builtin_type_short =
1542     init_type (TYPE_CODE_INT, TARGET_SHORT_BIT / TARGET_CHAR_BIT, 0,
1543                "short");
1544   builtin_type_unsigned_short =
1545     init_type (TYPE_CODE_INT, TARGET_SHORT_BIT / TARGET_CHAR_BIT, 1,
1546                "unsigned short");
1547   builtin_type_int =
1548     init_type (TYPE_CODE_INT, TARGET_INT_BIT / TARGET_CHAR_BIT, 0,
1549                "int");
1550   builtin_type_unsigned_int =
1551     init_type (TYPE_CODE_INT, TARGET_INT_BIT / TARGET_CHAR_BIT, 1,
1552                "unsigned int");
1553   builtin_type_long =
1554     init_type (TYPE_CODE_INT, TARGET_LONG_BIT / TARGET_CHAR_BIT, 0,
1555                "long");
1556   builtin_type_unsigned_long =
1557     init_type (TYPE_CODE_INT, TARGET_LONG_BIT / TARGET_CHAR_BIT, 1,
1558                "unsigned long");
1559   builtin_type_long_long =
1560     init_type (TYPE_CODE_INT, TARGET_LONG_LONG_BIT / TARGET_CHAR_BIT, 0,
1561                "long long");
1562   builtin_type_unsigned_long_long = 
1563     init_type (TYPE_CODE_INT, TARGET_LONG_LONG_BIT / TARGET_CHAR_BIT, 1,
1564                "unsigned long long");
1565   builtin_type_float =
1566     init_type (TYPE_CODE_FLT, TARGET_FLOAT_BIT / TARGET_CHAR_BIT, 0,
1567                "float");
1568   builtin_type_double =
1569     init_type (TYPE_CODE_FLT, TARGET_DOUBLE_BIT / TARGET_CHAR_BIT, 0,
1570                "double");
1571   builtin_type_long_double =
1572     init_type (TYPE_CODE_FLT, TARGET_LONG_DOUBLE_BIT / TARGET_CHAR_BIT, 0,
1573                "long double");
1574   builtin_type_complex =
1575     init_type (TYPE_CODE_FLT, TARGET_COMPLEX_BIT / TARGET_CHAR_BIT, 0,
1576                "complex");
1577   builtin_type_double_complex =
1578     init_type (TYPE_CODE_FLT, TARGET_DOUBLE_COMPLEX_BIT / TARGET_CHAR_BIT, 0,
1579                "double complex");
1580
1581   add_language (&c_language_defn);
1582   add_language (&cplus_language_defn);
1583 }
This page took 0.118407 seconds and 4 git commands to generate.