BSD 4_4_Lite2 development
[unix-history] / usr / src / contrib / gcc-2.3.3 / objc-parse.y
CommitLineData
e531dfd8
C
1/* YACC parser for C syntax and for Objective C. -*-c-*-
2 Copyright (C) 1987, 1988, 1989, 1992 Free Software Foundation, Inc.
3
4This file is part of GNU CC.
5
6GNU CC is free software; you can redistribute it and/or modify
7it under the terms of the GNU General Public License as published by
8the Free Software Foundation; either version 2, or (at your option)
9any later version.
10
11GNU CC is distributed in the hope that it will be useful,
12but WITHOUT ANY WARRANTY; without even the implied warranty of
13MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
14GNU General Public License for more details.
15
16You should have received a copy of the GNU General Public License
17along with GNU CC; see the file COPYING. If not, write to
18the Free Software Foundation, 675 Mass Ave, Cambridge, MA 02139, USA. */
19
20/* This file defines the grammar of C and that of Objective C.
21 ifobjc ... end ifobjc conditionals contain code for Objective C only.
22 ifc ... end ifc conditionals contain code for C only.
23 The awk script cond.awk is used to convert this file into
24 c-parse.y and into objc-parse.y. */
25
26/* To whomever it may concern: I have heard that such a thing was once
27written by AT&T, but I have never seen it. */
28
29%expect 56
30
31%{
32#include <stdio.h>
33#include <errno.h>
34#include <setjmp.h>
35
36#include "config.h"
37#include "tree.h"
38#include "input.h"
39#include "c-lex.h"
40#include "c-tree.h"
41#include "flags.h"
42
43#ifdef MULTIBYTE_CHARS
44#include <stdlib.h>
45#include <locale.h>
46#endif
47
48#include "objc-actions.h"
49
50#ifndef errno
51extern int errno;
52#endif
53
54void yyerror ();
55
56/* Like YYERROR but do call yyerror. */
57#define YYERROR1 { yyerror ("syntax error"); YYERROR; }
58
59/* Cause the `yydebug' variable to be defined. */
60#define YYDEBUG 1
61%}
62
63%start program
64
65%union {long itype; tree ttype; enum tree_code code;
66 char *filename; int lineno; }
67
68/* All identifiers that are not reserved words
69 and are not declared typedefs in the current block */
70%token IDENTIFIER
71
72/* All identifiers that are declared typedefs in the current block.
73 In some contexts, they are treated just like IDENTIFIER,
74 but they can also serve as typespecs in declarations. */
75%token TYPENAME
76
77/* Reserved words that specify storage class.
78 yylval contains an IDENTIFIER_NODE which indicates which one. */
79%token SCSPEC
80
81/* Reserved words that specify type.
82 yylval contains an IDENTIFIER_NODE which indicates which one. */
83%token TYPESPEC
84
85/* Reserved words that qualify type: "const" or "volatile".
86 yylval contains an IDENTIFIER_NODE which indicates which one. */
87%token TYPE_QUAL
88
89/* Character or numeric constants.
90 yylval is the node for the constant. */
91%token CONSTANT
92
93/* String constants in raw form.
94 yylval is a STRING_CST node. */
95%token STRING
96
97/* "...", used for functions with variable arglists. */
98%token ELLIPSIS
99
100/* the reserved words */
101/* SCO include files test "ASM", so use something else. */
102%token SIZEOF ENUM STRUCT UNION IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
103%token BREAK CONTINUE RETURN GOTO ASM_KEYWORD TYPEOF ALIGNOF ALIGN
104%token ATTRIBUTE EXTENSION LABEL
105
106/* Add precedence rules to solve dangling else s/r conflict */
107%nonassoc IF
108%nonassoc ELSE
109
110/* Define the operator tokens and their precedences.
111 The value is an integer because, if used, it is the tree code
112 to use in the expression made from the operator. */
113
114%right <code> ASSIGN '='
115%right <code> '?' ':'
116%left <code> OROR
117%left <code> ANDAND
118%left <code> '|'
119%left <code> '^'
120%left <code> '&'
121%left <code> EQCOMPARE
122%left <code> ARITHCOMPARE
123%left <code> LSHIFT RSHIFT
124%left <code> '+' '-'
125%left <code> '*' '/' '%'
126%right <code> UNARY PLUSPLUS MINUSMINUS
127%left HYPERUNARY
128%left <code> POINTSAT '.' '(' '['
129
130/* The Objective-C keywords. These are included in C and in
131 Objective C, so that the token codes are the same in both. */
132%token INTERFACE IMPLEMENTATION END SELECTOR DEFS ENCODE
133%token CLASSNAME PUBLIC
134
135
136%type <code> unop
137
138%type <ttype> identifier IDENTIFIER TYPENAME CONSTANT expr nonnull_exprlist exprlist
139%type <ttype> expr_no_commas cast_expr unary_expr primary string STRING
140%type <ttype> typed_declspecs reserved_declspecs
141%type <ttype> typed_typespecs reserved_typespecquals
142%type <ttype> declmods typespec typespecqual_reserved
143%type <ttype> SCSPEC TYPESPEC TYPE_QUAL nonempty_type_quals maybe_type_qual
144%type <ttype> initdecls notype_initdecls initdcl notype_initdcl
145%type <ttype> init initlist maybeasm
146%type <ttype> asm_operands nonnull_asm_operands asm_operand asm_clobbers
147%type <ttype> maybe_attribute attribute_list attrib
148
149%type <ttype> compstmt
150
151%type <ttype> declarator
152%type <ttype> notype_declarator after_type_declarator
153%type <ttype> parm_declarator
154
155%type <ttype> structsp component_decl_list component_decl_list2
156%type <ttype> component_decl components component_declarator
157%type <ttype> enumlist enumerator
158%type <ttype> typename absdcl absdcl1 type_quals
159%type <ttype> xexpr parms parm identifiers
160
161%type <ttype> parmlist parmlist_1 parmlist_2
162%type <ttype> parmlist_or_identifiers parmlist_or_identifiers_1
163%type <ttype> identifiers_or_typenames
164
165%type <itype> setspecs
166
167%type <filename> save_filename
168%type <lineno> save_lineno
169\f
170/* the Objective-C nonterminals */
171
172%type <ttype> ivar_decl_list ivar_decls ivar_decl ivars ivar_declarator
173%type <ttype> methoddecl unaryselector keywordselector selector
174%type <ttype> keyworddecl receiver objcmessageexpr messageargs
175%type <ttype> keywordexpr keywordarglist keywordarg
176%type <ttype> myparms myparm optparmlist reservedwords objcselectorexpr
177%type <ttype> selectorarg keywordnamelist keywordname objcencodeexpr
178%type <ttype> CLASSNAME
179\f
180%{
181/* Number of statements (loosely speaking) seen so far. */
182static int stmt_count;
183
184/* Input file and line number of the end of the body of last simple_if;
185 used by the stmt-rule immediately after simple_if returns. */
186static char *if_stmt_file;
187static int if_stmt_line;
188
189/* List of types and structure classes of the current declaration. */
190static tree current_declspecs;
191
192/* Stack of saved values of current_declspecs. */
193static tree declspec_stack;
194
195/* 1 if we explained undeclared var errors. */
196static int undeclared_variable_notice;
197
198/* Objective-C specific information */
199
200tree objc_interface_context;
201tree objc_implementation_context;
202tree objc_method_context;
203tree objc_ivar_chain;
204tree objc_ivar_context;
205enum tree_code objc_inherit_code;
206int objc_receiver_context;
207int objc_public_flag;
208
209
210/* Tell yyparse how to print a token's value, if yydebug is set. */
211
212#define YYPRINT(FILE,YYCHAR,YYLVAL) yyprint(FILE,YYCHAR,YYLVAL)
213extern void yyprint ();
214%}
215\f
216%%
217program: /* empty */
218 { if (pedantic)
219 pedwarn ("ANSI C forbids an empty source file");
220 objc_finish ();
221 }
222 | extdefs
223 {
224 objc_finish ();
225 }
226 ;
227
228/* the reason for the strange actions in this rule
229 is so that notype_initdecls when reached via datadef
230 can find a valid list of type and sc specs in $0. */
231
232extdefs:
233 {$<ttype>$ = NULL_TREE; } extdef
234 | extdefs {$<ttype>$ = NULL_TREE; } extdef
235 ;
236
237extdef:
238 fndef
239 | datadef
240 | objcdef
241 | ASM_KEYWORD '(' expr ')' ';'
242 { STRIP_NOPS ($3);
243 if ((TREE_CODE ($3) == ADDR_EXPR
244 && TREE_CODE (TREE_OPERAND ($3, 0)) == STRING_CST)
245 || TREE_CODE ($3) == STRING_CST)
246 assemble_asm ($3);
247 else
248 error ("argument of `asm' is not a constant string"); }
249 ;
250
251datadef:
252 setspecs notype_initdecls ';'
253 { if (pedantic)
254 error ("ANSI C forbids data definition with no type or storage class");
255 else if (!flag_traditional)
256 warning ("data definition has no type or storage class"); }
257 | declmods setspecs notype_initdecls ';'
258 {}
259 | typed_declspecs setspecs initdecls ';'
260 {}
261 | declmods ';'
262 { pedwarn ("empty declaration"); }
263 | typed_declspecs ';'
264 { shadow_tag ($1); }
265 | error ';'
266 | error '}'
267 | ';'
268 { if (pedantic)
269 pedwarn ("ANSI C does not allow extra `;' outside of a function"); }
270 ;
271\f
272fndef:
273 typed_declspecs setspecs declarator
274 { if (! start_function ($1, $3, 0))
275 YYERROR1;
276 reinit_parse_for_function (); }
277 xdecls
278 { store_parm_decls (); }
279 compstmt_or_error
280 { finish_function (0); }
281 | typed_declspecs setspecs declarator error
282 { }
283 | declmods setspecs notype_declarator
284 { if (! start_function ($1, $3, 0))
285 YYERROR1;
286 reinit_parse_for_function (); }
287 xdecls
288 { store_parm_decls (); }
289 compstmt_or_error
290 { finish_function (0); }
291 | declmods setspecs notype_declarator error
292 { }
293 | setspecs notype_declarator
294 { if (! start_function (NULL_TREE, $2, 0))
295 YYERROR1;
296 reinit_parse_for_function (); }
297 xdecls
298 { store_parm_decls (); }
299 compstmt_or_error
300 { finish_function (0); }
301 | setspecs notype_declarator error
302 { }
303 ;
304
305identifier:
306 IDENTIFIER
307 | TYPENAME
308 | CLASSNAME
309 { $$ = CLASS_NAME ($1); }
310 ;
311
312unop: '&'
313 { $$ = ADDR_EXPR; }
314 | '-'
315 { $$ = NEGATE_EXPR; }
316 | '+'
317 { $$ = CONVERT_EXPR; }
318 | PLUSPLUS
319 { $$ = PREINCREMENT_EXPR; }
320 | MINUSMINUS
321 { $$ = PREDECREMENT_EXPR; }
322 | '~'
323 { $$ = BIT_NOT_EXPR; }
324 | '!'
325 { $$ = TRUTH_NOT_EXPR; }
326 ;
327
328expr: nonnull_exprlist
329 { $$ = build_compound_expr ($1); }
330 ;
331
332exprlist:
333 /* empty */
334 { $$ = NULL_TREE; }
335 | nonnull_exprlist
336 ;
337
338nonnull_exprlist:
339 expr_no_commas
340 { $$ = build_tree_list (NULL_TREE, $1); }
341 | nonnull_exprlist ',' expr_no_commas
342 { chainon ($1, build_tree_list (NULL_TREE, $3)); }
343 ;
344
345unary_expr:
346 primary
347 | '*' cast_expr %prec UNARY
348 { $$ = build_indirect_ref ($2, "unary *"); }
349 /* __extension__ turns off -pedantic for following primary. */
350 | EXTENSION
351 { $<itype>1 = pedantic;
352 pedantic = 0; }
353 cast_expr %prec UNARY
354 { $$ = $3;
355 pedantic = $<itype>1; }
356 | unop cast_expr %prec UNARY
357 { $$ = build_unary_op ($1, $2, 0); }
358 /* Refer to the address of a label as a pointer. */
359 | ANDAND identifier
360 { tree label = lookup_label ($2);
361 TREE_USED (label) = 1;
362 $$ = build1 (ADDR_EXPR, ptr_type_node, label);
363 TREE_CONSTANT ($$) = 1; }
364/* This seems to be impossible on some machines, so let's turn it off.
365 You can use __builtin_next_arg to find the anonymous stack args.
366 | '&' ELLIPSIS
367 { tree types = TYPE_ARG_TYPES (TREE_TYPE (current_function_decl));
368 $$ = error_mark_node;
369 if (TREE_VALUE (tree_last (types)) == void_type_node)
370 error ("`&...' used in function with fixed number of arguments");
371 else
372 {
373 if (pedantic)
374 pedwarn ("ANSI C forbids `&...'");
375 $$ = tree_last (DECL_ARGUMENTS (current_function_decl));
376 $$ = build_unary_op (ADDR_EXPR, $$, 0);
377 } }
378*/
379 | SIZEOF unary_expr %prec UNARY
380 { if (TREE_CODE ($2) == COMPONENT_REF
381 && DECL_BIT_FIELD (TREE_OPERAND ($2, 1)))
382 error ("`sizeof' applied to a bit-field");
383 $$ = c_sizeof (TREE_TYPE ($2)); }
384 | SIZEOF '(' typename ')' %prec HYPERUNARY
385 { $$ = c_sizeof (groktypename ($3)); }
386 | ALIGNOF unary_expr %prec UNARY
387 { $$ = c_alignof_expr ($2); }
388 | ALIGNOF '(' typename ')' %prec HYPERUNARY
389 { $$ = c_alignof (groktypename ($3)); }
390 ;
391
392cast_expr:
393 unary_expr
394 | '(' typename ')' cast_expr %prec UNARY
395 { tree type = groktypename ($2);
396 $$ = build_c_cast (type, $4); }
397 | '(' typename ')' '{' initlist maybecomma '}' %prec UNARY
398 { tree type = groktypename ($2);
399 char *name;
400 if (pedantic)
401 pedwarn ("ANSI C forbids constructor expressions");
402 if (TYPE_NAME (type) != 0)
403 {
404 if (TREE_CODE (TYPE_NAME (type)) == IDENTIFIER_NODE)
405 name = IDENTIFIER_POINTER (TYPE_NAME (type));
406 else
407 name = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (type)));
408 }
409 else
410 name = "";
411 $$ = digest_init (type, build_nt (CONSTRUCTOR, NULL_TREE, nreverse ($5)),
412 NULL_PTR, 0, 0, name);
413 if (TREE_CODE (type) == ARRAY_TYPE && TYPE_SIZE (type) == 0)
414 {
415 int failure = complete_array_type (type, $$, 1);
416 if (failure)
417 abort ();
418 }
419 }
420 ;
421
422expr_no_commas:
423 cast_expr
424 | expr_no_commas '+' expr_no_commas
425 { $$ = parser_build_binary_op ($2, $1, $3); }
426 | expr_no_commas '-' expr_no_commas
427 { $$ = parser_build_binary_op ($2, $1, $3); }
428 | expr_no_commas '*' expr_no_commas
429 { $$ = parser_build_binary_op ($2, $1, $3); }
430 | expr_no_commas '/' expr_no_commas
431 { $$ = parser_build_binary_op ($2, $1, $3); }
432 | expr_no_commas '%' expr_no_commas
433 { $$ = parser_build_binary_op ($2, $1, $3); }
434 | expr_no_commas LSHIFT expr_no_commas
435 { $$ = parser_build_binary_op ($2, $1, $3); }
436 | expr_no_commas RSHIFT expr_no_commas
437 { $$ = parser_build_binary_op ($2, $1, $3); }
438 | expr_no_commas ARITHCOMPARE expr_no_commas
439 { $$ = parser_build_binary_op ($2, $1, $3); }
440 | expr_no_commas EQCOMPARE expr_no_commas
441 { $$ = parser_build_binary_op ($2, $1, $3); }
442 | expr_no_commas '&' expr_no_commas
443 { $$ = parser_build_binary_op ($2, $1, $3); }
444 | expr_no_commas '|' expr_no_commas
445 { $$ = parser_build_binary_op ($2, $1, $3); }
446 | expr_no_commas '^' expr_no_commas
447 { $$ = parser_build_binary_op ($2, $1, $3); }
448 | expr_no_commas ANDAND expr_no_commas
449 { $$ = parser_build_binary_op (TRUTH_ANDIF_EXPR, $1, $3); }
450 | expr_no_commas OROR expr_no_commas
451 { $$ = parser_build_binary_op (TRUTH_ORIF_EXPR, $1, $3); }
452 | expr_no_commas '?' xexpr ':' expr_no_commas
453 { $$ = build_conditional_expr ($1, $3, $5); }
454 | expr_no_commas '=' expr_no_commas
455 { $$ = build_modify_expr ($1, NOP_EXPR, $3);
456 C_SET_EXP_ORIGINAL_CODE ($$, MODIFY_EXPR); }
457 | expr_no_commas ASSIGN expr_no_commas
458 { $$ = build_modify_expr ($1, $2, $3);
459 C_SET_EXP_ORIGINAL_CODE ($$, MODIFY_EXPR); }
460 ;
461
462primary:
463 IDENTIFIER
464 {
465 tree context;
466
467 $$ = lastiddecl;
468 if (!$$ || $$ == error_mark_node)
469 {
470 if (yychar == YYEMPTY)
471 yychar = YYLEX;
472 if (yychar == '(')
473 {
474 if (objc_receiver_context
475 && ! (objc_receiver_context
476 && strcmp (IDENTIFIER_POINTER ($1), "super")))
477 /* we have a message to super */
478 $$ = get_super_receiver ();
479 else if (objc_method_context
480 && is_ivar (objc_ivar_chain, $1))
481 $$ = build_ivar_reference ($1);
482 else
483 {
484 /* Ordinary implicit function declaration. */
485 $$ = implicitly_declare ($1);
486 assemble_external ($$);
487 TREE_USED ($$) = 1;
488 }
489 }
490 else if (current_function_decl == 0)
491 {
492 error ("`%s' undeclared, outside of functions",
493 IDENTIFIER_POINTER ($1));
494 $$ = error_mark_node;
495 }
496 else
497 {
498 if (objc_receiver_context
499 && ! strcmp (IDENTIFIER_POINTER ($1), "super"))
500 /* we have a message to super */
501 $$ = get_super_receiver ();
502 else if (objc_method_context
503 && is_ivar (objc_ivar_chain, $1))
504 $$ = build_ivar_reference ($1);
505 else
506 {
507 if (IDENTIFIER_GLOBAL_VALUE ($1) != error_mark_node
508 || IDENTIFIER_ERROR_LOCUS ($1) != current_function_decl)
509 {
510 error ("`%s' undeclared (first use this function)",
511 IDENTIFIER_POINTER ($1));
512
513 if (! undeclared_variable_notice)
514 {
515 error ("(Each undeclared identifier is reported only once");
516 error ("for each function it appears in.)");
517 undeclared_variable_notice = 1;
518 }
519 }
520 $$ = error_mark_node;
521 /* Prevent repeated error messages. */
522 IDENTIFIER_GLOBAL_VALUE ($1) = error_mark_node;
523 IDENTIFIER_ERROR_LOCUS ($1) = current_function_decl;
524 }
525 }
526 }
527 else if (TREE_TYPE ($$) == error_mark_node)
528 $$ = error_mark_node;
529 else if (C_DECL_ANTICIPATED ($$))
530 {
531 /* The first time we see a build-in function used,
532 if it has not been declared. */
533 C_DECL_ANTICIPATED ($$) = 0;
534 if (yychar == YYEMPTY)
535 yychar = YYLEX;
536 if (yychar == '(')
537 {
538 /* Omit the implicit declaration we
539 would ordinarily do, so we don't lose
540 the actual built in type.
541 But print a diagnostic for the mismatch. */
542 if (objc_method_context
543 && is_ivar (objc_ivar_chain, $1))
544 error ("Instance variable `%s' implicitly declared as function",
545 IDENTIFIER_POINTER (DECL_NAME ($$)));
546 else
547 if (TREE_CODE ($$) != FUNCTION_DECL)
548 error ("`%s' implicitly declared as function",
549 IDENTIFIER_POINTER (DECL_NAME ($$)));
550 else if ((TYPE_MODE (TREE_TYPE (TREE_TYPE ($$)))
551 != TYPE_MODE (integer_type_node))
552 && (TREE_TYPE (TREE_TYPE ($$))
553 != void_type_node))
554 pedwarn ("type mismatch in implicit declaration for built-in function `%s'",
555 IDENTIFIER_POINTER (DECL_NAME ($$)));
556 /* If it really returns void, change that to int. */
557 if (TREE_TYPE (TREE_TYPE ($$)) == void_type_node)
558 TREE_TYPE ($$)
559 = build_function_type (integer_type_node,
560 TYPE_ARG_TYPES (TREE_TYPE ($$)));
561 }
562 else
563 pedwarn ("built-in function `%s' used without declaration",
564 IDENTIFIER_POINTER (DECL_NAME ($$)));
565
566 /* Do what we would ordinarily do when a fn is used. */
567 assemble_external ($$);
568 TREE_USED ($$) = 1;
569 }
570 else
571 {
572 assemble_external ($$);
573 TREE_USED ($$) = 1;
574 /* we have a definition - still check if iVariable */
575
576 if (!objc_receiver_context
577 || (objc_receiver_context
578 && strcmp (IDENTIFIER_POINTER ($1), "super")))
579 {
580 if (objc_method_context
581 && is_ivar (objc_ivar_chain, $1))
582 {
583 if (IDENTIFIER_LOCAL_VALUE ($1))
584 warning ("local declaration of `%s' hides instance variable",
585 IDENTIFIER_POINTER ($1));
586 else
587 $$ = build_ivar_reference ($1);
588 }
589 }
590 else /* we have a message to super */
591 $$ = get_super_receiver ();
592 }
593
594 if (TREE_CODE ($$) == CONST_DECL)
595 {
596 $$ = DECL_INITIAL ($$);
597 /* This is to prevent an enum whose value is 0
598 from being considered a null pointer constant. */
599 $$ = build1 (NOP_EXPR, TREE_TYPE ($$), $$);
600 TREE_CONSTANT ($$) = 1;
601 }
602 }
603 | CONSTANT
604 | string
605 { $$ = combine_strings ($1); }
606 | '(' expr ')'
607 { char class = TREE_CODE_CLASS (TREE_CODE ($2));
608 if (class == 'e' || class == '1'
609 || class == '2' || class == '<')
610 C_SET_EXP_ORIGINAL_CODE ($2, ERROR_MARK);
611 $$ = $2; }
612 | '(' error ')'
613 { $$ = error_mark_node; }
614 | '('
615 { if (current_function_decl == 0)
616 {
617 error ("braced-group within expression allowed only inside a function");
618 YYERROR;
619 }
620 /* We must force a BLOCK for this level
621 so that, if it is not expanded later,
622 there is a way to turn off the entire subtree of blocks
623 that are contained in it. */
624 keep_next_level ();
625 push_label_level ();
626 $<ttype>$ = expand_start_stmt_expr (); }
627 compstmt ')'
628 { tree rtl_exp;
629 if (pedantic)
630 pedwarn ("ANSI C forbids braced-groups within expressions");
631 pop_label_level ();
632 rtl_exp = expand_end_stmt_expr ($<ttype>2);
633 /* The statements have side effects, so the group does. */
634 TREE_SIDE_EFFECTS (rtl_exp) = 1;
635
636 /* Make a BIND_EXPR for the BLOCK already made. */
637 $$ = build (BIND_EXPR, TREE_TYPE (rtl_exp),
638 NULL_TREE, rtl_exp, $3);
639 /* Remove the block from the tree at this point.
640 It gets put back at the proper place
641 when the BIND_EXPR is expanded. */
642 delete_block ($3);
643 }
644 | primary '(' exprlist ')' %prec '.'
645 { $$ = build_function_call ($1, $3); }
646 | primary '[' expr ']' %prec '.'
647 { $$ = build_array_ref ($1, $3); }
648 | primary '.' identifier
649 {
650 if (doing_objc_thang)
651 {
652 if (is_public ($1, $3))
653 $$ = build_component_ref ($1, $3);
654 else
655 $$ = error_mark_node;
656 }
657 else
658 $$ = build_component_ref ($1, $3);
659 }
660 | primary POINTSAT identifier
661 {
662 tree expr = build_indirect_ref ($1, "->");
663
664 if (doing_objc_thang)
665 {
666 if (is_public (expr, $3))
667 $$ = build_component_ref (expr, $3);
668 else
669 $$ = error_mark_node;
670 }
671 else
672 $$ = build_component_ref (expr, $3);
673 }
674 | primary PLUSPLUS
675 { $$ = build_unary_op (POSTINCREMENT_EXPR, $1, 0); }
676 | primary MINUSMINUS
677 { $$ = build_unary_op (POSTDECREMENT_EXPR, $1, 0); }
678 | objcmessageexpr
679 { $$ = build_message_expr ($1); }
680 | objcselectorexpr
681 { $$ = build_selector_expr ($1); }
682 | objcencodeexpr
683 { $$ = build_encode_expr ($1); }
684 ;
685
686/* Produces a STRING_CST with perhaps more STRING_CSTs chained onto it. */
687string:
688 STRING
689 | string STRING
690 { $$ = chainon ($1, $2); }
691 ;
692
693xdecls:
694 /* empty */
695 | datadecls
696 | datadecls ELLIPSIS
697 /* ... is used here to indicate a varargs function. */
698 { c_mark_varargs ();
699 if (pedantic)
700 pedwarn ("ANSI C does not permit use of `varargs.h'"); }
701 ;
702
703/* The following are analogous to lineno_decl, decls and decl
704 except that they do not allow nested functions.
705 They are used for old-style parm decls. */
706lineno_datadecl:
707 save_filename save_lineno datadecl
708 { }
709 ;
710
711datadecls:
712 lineno_datadecl
713 | errstmt
714 | datadecls lineno_datadecl
715 | lineno_datadecl errstmt
716 ;
717
718datadecl:
719 typed_declspecs setspecs initdecls ';'
720 { current_declspecs = TREE_VALUE (declspec_stack);
721 declspec_stack = TREE_CHAIN (declspec_stack);
722 resume_momentary ($2); }
723 | declmods setspecs notype_initdecls ';'
724 { current_declspecs = TREE_VALUE (declspec_stack);
725 declspec_stack = TREE_CHAIN (declspec_stack);
726 resume_momentary ($2); }
727 | typed_declspecs ';'
728 { shadow_tag_warned ($1, 1);
729 pedwarn ("empty declaration"); }
730 | declmods ';'
731 { pedwarn ("empty declaration"); }
732 ;
733
734/* This combination which saves a lineno before a decl
735 is the normal thing to use, rather than decl itself.
736 This is to avoid shift/reduce conflicts in contexts
737 where statement labels are allowed. */
738lineno_decl:
739 save_filename save_lineno decl
740 { }
741 ;
742
743decls:
744 lineno_decl
745 | errstmt
746 | decls lineno_decl
747 | lineno_decl errstmt
748 ;
749
750/* records the type and storage class specs to use for processing
751 the declarators that follow.
752 Maintains a stack of outer-level values of current_declspecs,
753 for the sake of parm declarations nested in function declarators. */
754setspecs: /* empty */
755 { $$ = suspend_momentary ();
756 pending_xref_error ();
757 declspec_stack = tree_cons (NULL_TREE, current_declspecs,
758 declspec_stack);
759 current_declspecs = $<ttype>0; }
760 ;
761
762decl:
763 typed_declspecs setspecs initdecls ';'
764 { current_declspecs = TREE_VALUE (declspec_stack);
765 declspec_stack = TREE_CHAIN (declspec_stack);
766 resume_momentary ($2); }
767 | declmods setspecs notype_initdecls ';'
768 { current_declspecs = TREE_VALUE (declspec_stack);
769 declspec_stack = TREE_CHAIN (declspec_stack);
770 resume_momentary ($2); }
771 | typed_declspecs setspecs nested_function
772 { current_declspecs = TREE_VALUE (declspec_stack);
773 declspec_stack = TREE_CHAIN (declspec_stack);
774 resume_momentary ($2); }
775 | declmods setspecs notype_nested_function
776 { current_declspecs = TREE_VALUE (declspec_stack);
777 declspec_stack = TREE_CHAIN (declspec_stack);
778 resume_momentary ($2); }
779 | typed_declspecs ';'
780 { shadow_tag ($1); }
781 | declmods ';'
782 { pedwarn ("empty declaration"); }
783 ;
784
785/* Declspecs which contain at least one type specifier or typedef name.
786 (Just `const' or `volatile' is not enough.)
787 A typedef'd name following these is taken as a name to be declared. */
788
789typed_declspecs:
790 typespec reserved_declspecs
791 { $$ = tree_cons (NULL_TREE, $1, $2); }
792 | declmods typespec reserved_declspecs
793 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
794 ;
795
796reserved_declspecs: /* empty */
797 { $$ = NULL_TREE; }
798 | reserved_declspecs typespecqual_reserved
799 { $$ = tree_cons (NULL_TREE, $2, $1); }
800 | reserved_declspecs SCSPEC
801 { if (extra_warnings)
802 warning ("`%s' is not at beginning of declaration",
803 IDENTIFIER_POINTER ($2));
804 $$ = tree_cons (NULL_TREE, $2, $1); }
805 ;
806
807/* List of just storage classes and type modifiers.
808 A declaration can start with just this, but then it cannot be used
809 to redeclare a typedef-name. */
810
811declmods:
812 TYPE_QUAL
813 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
814 TREE_STATIC ($$) = 1; }
815 | SCSPEC
816 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
817 | declmods TYPE_QUAL
818 { $$ = tree_cons (NULL_TREE, $2, $1);
819 TREE_STATIC ($$) = 1; }
820 | declmods SCSPEC
821 { if (extra_warnings && TREE_STATIC ($1))
822 warning ("`%s' is not at beginning of declaration",
823 IDENTIFIER_POINTER ($2));
824 $$ = tree_cons (NULL_TREE, $2, $1);
825 TREE_STATIC ($$) = TREE_STATIC ($1); }
826 ;
827
828
829/* Used instead of declspecs where storage classes are not allowed
830 (that is, for typenames and structure components).
831 Don't accept a typedef-name if anything but a modifier precedes it. */
832
833typed_typespecs:
834 typespec reserved_typespecquals
835 { $$ = tree_cons (NULL_TREE, $1, $2); }
836 | nonempty_type_quals typespec reserved_typespecquals
837 { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
838 ;
839
840reserved_typespecquals: /* empty */
841 { $$ = NULL_TREE; }
842 | reserved_typespecquals typespecqual_reserved
843 { $$ = tree_cons (NULL_TREE, $2, $1); }
844 ;
845
846/* A typespec (but not a type qualifier).
847 Once we have seen one of these in a declaration,
848 if a typedef name appears then it is being redeclared. */
849
850typespec: TYPESPEC
851 | structsp
852 | TYPENAME
853 { /* For a typedef name, record the meaning, not the name.
854 In case of `foo foo, bar;'. */
855 $$ = lookup_name ($1); }
856 | CLASSNAME
857 { $$ = get_static_reference ($1); }
858 | TYPEOF '(' expr ')'
859 { $$ = TREE_TYPE ($3); }
860 | TYPEOF '(' typename ')'
861 { $$ = groktypename ($3); }
862 ;
863
864/* A typespec that is a reserved word, or a type qualifier. */
865
866typespecqual_reserved: TYPESPEC
867 | TYPE_QUAL
868 | structsp
869 ;
870
871initdecls:
872 initdcl
873 | initdecls ',' initdcl
874 ;
875
876notype_initdecls:
877 notype_initdcl
878 | notype_initdecls ',' initdcl
879 ;
880
881maybeasm:
882 /* empty */
883 { $$ = NULL_TREE; }
884 | ASM_KEYWORD '(' string ')'
885 { if (TREE_CHAIN ($3)) $3 = combine_strings ($3);
886 $$ = $3;
887 }
888 ;
889
890initdcl:
891 declarator maybeasm maybe_attribute '='
892 { $<ttype>$ = start_decl ($1, current_declspecs, 1); }
893 init
894/* Note how the declaration of the variable is in effect while its init is parsed! */
895 { decl_attributes ($<ttype>5, $3);
896 finish_decl ($<ttype>5, $6, $2); }
897 | declarator maybeasm maybe_attribute
898 { tree d = start_decl ($1, current_declspecs, 0);
899 decl_attributes (d, $3);
900 finish_decl (d, NULL_TREE, $2); }
901 ;
902
903notype_initdcl:
904 notype_declarator maybeasm maybe_attribute '='
905 { $<ttype>$ = start_decl ($1, current_declspecs, 1); }
906 init
907/* Note how the declaration of the variable is in effect while its init is parsed! */
908 { decl_attributes ($<ttype>5, $3);
909 finish_decl ($<ttype>5, $6, $2); }
910 | notype_declarator maybeasm maybe_attribute
911 { tree d = start_decl ($1, current_declspecs, 0);
912 decl_attributes (d, $3);
913 finish_decl (d, NULL_TREE, $2); }
914 ;
915/* the * rules are dummies to accept the Apollo extended syntax
916 so that the header files compile. */
917maybe_attribute:
918 /* empty */
919 { $$ = NULL_TREE; }
920 | ATTRIBUTE '(' '(' attribute_list ')' ')'
921 { $$ = $4; }
922 ;
923
924attribute_list
925 : attrib
926 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
927 | attribute_list ',' attrib
928 { $$ = tree_cons (NULL_TREE, $3, $1); }
929 ;
930
931attrib
932 : IDENTIFIER
933 { if (strcmp (IDENTIFIER_POINTER ($1), "packed"))
934 warning ("`%s' attribute directive ignored",
935 IDENTIFIER_POINTER ($1));
936 $$ = $1; }
937 | IDENTIFIER '(' IDENTIFIER ')'
938 { /* If not "mode (m)", then issue warning. */
939 if (strcmp (IDENTIFIER_POINTER ($1), "mode") != 0)
940 {
941 warning ("`%s' attribute directive ignored",
942 IDENTIFIER_POINTER ($1));
943 $$ = $1;
944 }
945 else
946 $$ = tree_cons ($1, $3, NULL_TREE); }
947 | IDENTIFIER '(' CONSTANT ')'
948 { /* if not "aligned(n)", then issue warning */
949 if (strcmp (IDENTIFIER_POINTER ($1), "aligned") != 0
950 || TREE_CODE ($3) != INTEGER_CST)
951 {
952 warning ("`%s' attribute directive ignored",
953 IDENTIFIER_POINTER ($1));
954 $$ = $1;
955 }
956 else
957 $$ = tree_cons ($1, $3, NULL_TREE); }
958 | IDENTIFIER '(' IDENTIFIER ',' CONSTANT ',' CONSTANT ')'
959 { /* if not "format(...)", then issue warning */
960 if (strcmp (IDENTIFIER_POINTER ($1), "format") != 0
961 || TREE_CODE ($5) != INTEGER_CST
962 || TREE_CODE ($7) != INTEGER_CST)
963 {
964 warning ("`%s' attribute directive ignored",
965 IDENTIFIER_POINTER ($1));
966 $$ = $1;
967 }
968 else
969 $$ = tree_cons ($1,
970 tree_cons ($3,
971 tree_cons ($5, $7, NULL_TREE),
972 NULL_TREE),
973 NULL_TREE); }
974 ;
975
976init:
977 expr_no_commas
978 | '{' '}'
979 { $$ = build_nt (CONSTRUCTOR, NULL_TREE, NULL_TREE);
980 if (pedantic)
981 pedwarn ("ANSI C forbids empty initializer braces"); }
982 | '{' initlist '}'
983 { $$ = build_nt (CONSTRUCTOR, NULL_TREE, nreverse ($2)); }
984 | '{' initlist ',' '}'
985 { $$ = build_nt (CONSTRUCTOR, NULL_TREE, nreverse ($2)); }
986 | error
987 { $$ = NULL_TREE; }
988 ;
989
990/* This chain is built in reverse order,
991 and put in forward order where initlist is used. */
992initlist:
993 init
994 { $$ = build_tree_list (NULL_TREE, $1); }
995 | initlist ',' init
996 { $$ = tree_cons (NULL_TREE, $3, $1); }
997 /* These are for labeled elements. */
998 | '[' expr_no_commas ELLIPSIS expr_no_commas ']' init
999 { $$ = build_tree_list (tree_cons ($2, NULL_TREE,
1000 build_tree_list ($4, NULL_TREE)),
1001 $6); }
1002 | initlist ',' '[' expr_no_commas ELLIPSIS expr_no_commas ']' init
1003 { $$ = tree_cons (tree_cons ($4, NULL_TREE,
1004 build_tree_list ($6, NULL_TREE)),
1005 $8,
1006 $1); }
1007 | '[' expr_no_commas ']' init
1008 { $$ = build_tree_list ($2, $4); }
1009 | initlist ',' '[' expr_no_commas ']' init
1010 { $$ = tree_cons ($4, $6, $1); }
1011 | identifier ':' init
1012 { $$ = build_tree_list ($1, $3); }
1013 | initlist ',' identifier ':' init
1014 { $$ = tree_cons ($3, $5, $1); }
1015 ;
1016
1017nested_function:
1018 declarator
1019 { push_c_function_context ();
1020 if (! start_function (current_declspecs, $1, 1))
1021 {
1022 pop_c_function_context ();
1023 YYERROR1;
1024 }
1025 reinit_parse_for_function ();
1026 store_parm_decls (); }
1027/* This used to use compstmt_or_error.
1028 That caused a bug with input `f(g) int g {}',
1029 where the use of YYERROR1 above caused an error
1030 which then was handled by compstmt_or_error.
1031 There followed a repeated execution of that same rule,
1032 which called YYERROR1 again, and so on. */
1033 compstmt
1034 { finish_function (1);
1035 pop_c_function_context (); }
1036 ;
1037
1038notype_nested_function:
1039 notype_declarator
1040 { push_c_function_context ();
1041 if (! start_function (current_declspecs, $1, 1))
1042 {
1043 pop_c_function_context ();
1044 YYERROR1;
1045 }
1046 reinit_parse_for_function ();
1047 store_parm_decls (); }
1048/* This used to use compstmt_or_error.
1049 That caused a bug with input `f(g) int g {}',
1050 where the use of YYERROR1 above caused an error
1051 which then was handled by compstmt_or_error.
1052 There followed a repeated execution of that same rule,
1053 which called YYERROR1 again, and so on. */
1054 compstmt
1055 { finish_function (1);
1056 pop_c_function_context (); }
1057 ;
1058
1059/* Any kind of declarator (thus, all declarators allowed
1060 after an explicit typespec). */
1061
1062declarator:
1063 after_type_declarator
1064 | notype_declarator
1065 ;
1066
1067/* A declarator that is allowed only after an explicit typespec. */
1068
1069after_type_declarator:
1070 '(' after_type_declarator ')'
1071 { $$ = $2; }
1072 | after_type_declarator '(' parmlist_or_identifiers %prec '.'
1073 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1074/* | after_type_declarator '(' error ')' %prec '.'
1075 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1076 poplevel (0, 0, 0); } */
1077 | after_type_declarator '[' expr ']' %prec '.'
1078 { $$ = build_nt (ARRAY_REF, $1, $3); }
1079 | after_type_declarator '[' ']' %prec '.'
1080 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1081 | '*' type_quals after_type_declarator %prec UNARY
1082 { $$ = make_pointer_declarator ($2, $3); }
1083 | TYPENAME
1084 ;
1085
1086/* Kinds of declarator that can appear in a parameter list
1087 in addition to notype_declarator. This is like after_type_declarator
1088 but does not allow a typedef name in parentheses as an identifier
1089 (because it would conflict with a function with that typedef as arg). */
1090
1091parm_declarator:
1092 parm_declarator '(' parmlist_or_identifiers %prec '.'
1093 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1094/* | parm_declarator '(' error ')' %prec '.'
1095 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1096 poplevel (0, 0, 0); } */
1097 | parm_declarator '[' expr ']' %prec '.'
1098 { $$ = build_nt (ARRAY_REF, $1, $3); }
1099 | parm_declarator '[' ']' %prec '.'
1100 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1101 | '*' type_quals parm_declarator %prec UNARY
1102 { $$ = make_pointer_declarator ($2, $3); }
1103 | TYPENAME
1104 ;
1105
1106/* A declarator allowed whether or not there has been
1107 an explicit typespec. These cannot redeclare a typedef-name. */
1108
1109notype_declarator:
1110 notype_declarator '(' parmlist_or_identifiers %prec '.'
1111 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1112/* | notype_declarator '(' error ')' %prec '.'
1113 { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
1114 poplevel (0, 0, 0); } */
1115 | '(' notype_declarator ')'
1116 { $$ = $2; }
1117 | '*' type_quals notype_declarator %prec UNARY
1118 { $$ = make_pointer_declarator ($2, $3); }
1119 | notype_declarator '[' expr ']' %prec '.'
1120 { $$ = build_nt (ARRAY_REF, $1, $3); }
1121 | notype_declarator '[' ']' %prec '.'
1122 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1123 | IDENTIFIER
1124 ;
1125
1126structsp:
1127 STRUCT identifier '{'
1128 { $$ = start_struct (RECORD_TYPE, $2);
1129 /* Start scope of tag before parsing components. */
1130 }
1131 component_decl_list '}'
1132 { $$ = finish_struct ($<ttype>4, $5);
1133 /* Really define the structure. */
1134 }
1135 | STRUCT '{' component_decl_list '}'
1136 { $$ = finish_struct (start_struct (RECORD_TYPE, NULL_TREE),
1137 $3); }
1138 | STRUCT identifier
1139 { $$ = xref_tag (RECORD_TYPE, $2); }
1140 | UNION identifier '{'
1141 { $$ = start_struct (UNION_TYPE, $2); }
1142 component_decl_list '}'
1143 { $$ = finish_struct ($<ttype>4, $5); }
1144 | UNION '{' component_decl_list '}'
1145 { $$ = finish_struct (start_struct (UNION_TYPE, NULL_TREE),
1146 $3); }
1147 | UNION identifier
1148 { $$ = xref_tag (UNION_TYPE, $2); }
1149 | ENUM identifier '{'
1150 { $<itype>3 = suspend_momentary ();
1151 $$ = start_enum ($2); }
1152 enumlist maybecomma_warn '}'
1153 { $$ = finish_enum ($<ttype>4, nreverse ($5));
1154 resume_momentary ($<itype>3); }
1155 | ENUM '{'
1156 { $<itype>2 = suspend_momentary ();
1157 $$ = start_enum (NULL_TREE); }
1158 enumlist maybecomma_warn '}'
1159 { $$ = finish_enum ($<ttype>3, nreverse ($4));
1160 resume_momentary ($<itype>2); }
1161 | ENUM identifier
1162 { $$ = xref_tag (ENUMERAL_TYPE, $2); }
1163 ;
1164
1165maybecomma:
1166 /* empty */
1167 | ','
1168 ;
1169
1170maybecomma_warn:
1171 /* empty */
1172 | ','
1173 { if (pedantic) pedwarn ("comma at end of enumerator list"); }
1174 ;
1175
1176component_decl_list:
1177 component_decl_list2
1178 { $$ = $1; }
1179 | component_decl_list2 component_decl
1180 { $$ = chainon ($1, $2);
1181 pedwarn ("no semicolon at end of struct or union"); }
1182 ;
1183
1184component_decl_list2: /* empty */
1185 { $$ = NULL_TREE; }
1186 | component_decl_list2 component_decl ';'
1187 { $$ = chainon ($1, $2); }
1188 | component_decl_list2 ';'
1189 { if (pedantic)
1190 pedwarn ("extra semicolon in struct or union specified"); }
1191 /* foo(sizeof(struct{ @defs(ClassName)})); */
1192 | DEFS '(' CLASSNAME ')'
1193 { $$ = get_class_ivars ($3); }
1194 ;
1195
1196/* There is a shift-reduce conflict here, because `components' may
1197 start with a `typename'. It happens that shifting (the default resolution)
1198 does the right thing, because it treats the `typename' as part of
1199 a `typed_typespecs'.
1200
1201 It is possible that this same technique would allow the distinction
1202 between `notype_initdecls' and `initdecls' to be eliminated.
1203 But I am being cautious and not trying it. */
1204
1205component_decl:
1206 typed_typespecs setspecs components
1207 { $$ = $3;
1208 current_declspecs = TREE_VALUE (declspec_stack);
1209 declspec_stack = TREE_CHAIN (declspec_stack);
1210 resume_momentary ($2); }
1211 | typed_typespecs
1212 { if (pedantic)
1213 pedwarn ("ANSI C forbids member declarations with no members");
1214 shadow_tag($1);
1215 $$ = NULL_TREE; }
1216 | nonempty_type_quals setspecs components
1217 { $$ = $3;
1218 current_declspecs = TREE_VALUE (declspec_stack);
1219 declspec_stack = TREE_CHAIN (declspec_stack);
1220 resume_momentary ($2); }
1221 | nonempty_type_quals
1222 { if (pedantic)
1223 pedwarn ("ANSI C forbids member declarations with no members");
1224 shadow_tag($1);
1225 $$ = NULL_TREE; }
1226 | error
1227 { $$ = NULL_TREE; }
1228 ;
1229
1230components:
1231 component_declarator
1232 | components ',' component_declarator
1233 { $$ = chainon ($1, $3); }
1234 ;
1235
1236component_declarator:
1237 save_filename save_lineno declarator maybe_attribute
1238 { $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
1239 decl_attributes ($$, $4); }
1240 | save_filename save_lineno
1241 declarator ':' expr_no_commas maybe_attribute
1242 { $$ = grokfield ($1, $2, $3, current_declspecs, $5);
1243 decl_attributes ($$, $6); }
1244 | save_filename save_lineno ':' expr_no_commas
1245 { $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4); }
1246 ;
1247
1248/* We chain the enumerators in reverse order.
1249 They are put in forward order where enumlist is used.
1250 (The order used to be significant, but no longer is so.
1251 However, we still maintain the order, just to be clean.) */
1252
1253enumlist:
1254 enumerator
1255 | enumlist ',' enumerator
1256 { $$ = chainon ($3, $1); }
1257 ;
1258
1259
1260enumerator:
1261 identifier
1262 { $$ = build_enumerator ($1, NULL_TREE); }
1263 | identifier '=' expr_no_commas
1264 { $$ = build_enumerator ($1, $3); }
1265 ;
1266
1267typename:
1268 typed_typespecs absdcl
1269 { $$ = build_tree_list ($1, $2); }
1270 | nonempty_type_quals absdcl
1271 { $$ = build_tree_list ($1, $2); }
1272 ;
1273
1274absdcl: /* an absolute declarator */
1275 /* empty */
1276 { $$ = NULL_TREE; }
1277 | absdcl1
1278 ;
1279
1280nonempty_type_quals:
1281 TYPE_QUAL
1282 { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
1283 | nonempty_type_quals TYPE_QUAL
1284 { $$ = tree_cons (NULL_TREE, $2, $1); }
1285 ;
1286
1287type_quals:
1288 /* empty */
1289 { $$ = NULL_TREE; }
1290 | type_quals TYPE_QUAL
1291 { $$ = tree_cons (NULL_TREE, $2, $1); }
1292 ;
1293
1294absdcl1: /* a nonempty absolute declarator */
1295 '(' absdcl1 ')'
1296 { $$ = $2; }
1297 /* `(typedef)1' is `int'. */
1298 | '*' type_quals absdcl1 %prec UNARY
1299 { $$ = make_pointer_declarator ($2, $3); }
1300 | '*' type_quals %prec UNARY
1301 { $$ = make_pointer_declarator ($2, NULL_TREE); }
1302 | absdcl1 '(' parmlist %prec '.'
1303 { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
1304 | absdcl1 '[' expr ']' %prec '.'
1305 { $$ = build_nt (ARRAY_REF, $1, $3); }
1306 | absdcl1 '[' ']' %prec '.'
1307 { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
1308 | '(' parmlist %prec '.'
1309 { $$ = build_nt (CALL_EXPR, NULL_TREE, $2, NULL_TREE); }
1310 | '[' expr ']' %prec '.'
1311 { $$ = build_nt (ARRAY_REF, NULL_TREE, $2); }
1312 | '[' ']' %prec '.'
1313 { $$ = build_nt (ARRAY_REF, NULL_TREE, NULL_TREE); }
1314 ;
1315
1316/* at least one statement, the first of which parses without error. */
1317/* stmts is used only after decls, so an invalid first statement
1318 is actually regarded as an invalid decl and part of the decls. */
1319
1320stmts:
1321 lineno_stmt_or_label
1322 | stmts lineno_stmt_or_label
1323 | stmts errstmt
1324 ;
1325
1326xstmts:
1327 /* empty */
1328 | stmts
1329 ;
1330
1331errstmt: error ';'
1332 ;
1333
1334pushlevel: /* empty */
1335 { emit_line_note (input_filename, lineno);
1336 pushlevel (0);
1337 clear_last_expr ();
1338 push_momentary ();
1339 expand_start_bindings (0);
1340 if (objc_method_context)
1341 add_objc_decls ();
1342 }
1343 ;
1344
1345/* Read zero or more forward-declarations for labels
1346 that nested functions can jump to. */
1347maybe_label_decls:
1348 /* empty */
1349 | label_decls
1350 { if (pedantic)
1351 pedwarn ("ANSI C forbids label declarations"); }
1352 ;
1353
1354label_decls:
1355 label_decl
1356 | label_decls label_decl
1357 ;
1358
1359label_decl:
1360 LABEL identifiers_or_typenames ';'
1361 { tree link;
1362 for (link = $2; link; link = TREE_CHAIN (link))
1363 {
1364 tree label = shadow_label (TREE_VALUE (link));
1365 C_DECLARED_LABEL_FLAG (label) = 1;
1366 declare_nonlocal_label (label);
1367 }
1368 }
1369 ;
1370
1371/* This is the body of a function definition.
1372 It causes syntax errors to ignore to the next openbrace. */
1373compstmt_or_error:
1374 compstmt
1375 {}
1376 | error compstmt
1377 ;
1378
1379compstmt: '{' '}'
1380 { $$ = convert (void_type_node, integer_zero_node); }
1381 | '{' pushlevel maybe_label_decls decls xstmts '}'
1382 { emit_line_note (input_filename, lineno);
1383 expand_end_bindings (getdecls (), 1, 0);
1384 $$ = poplevel (1, 1, 0);
1385 pop_momentary (); }
1386 | '{' pushlevel maybe_label_decls error '}'
1387 { emit_line_note (input_filename, lineno);
1388 expand_end_bindings (getdecls (), kept_level_p (), 0);
1389 $$ = poplevel (kept_level_p (), 0, 0);
1390 pop_momentary (); }
1391 | '{' pushlevel maybe_label_decls stmts '}'
1392 { emit_line_note (input_filename, lineno);
1393 expand_end_bindings (getdecls (), kept_level_p (), 0);
1394 $$ = poplevel (kept_level_p (), 0, 0);
1395 pop_momentary (); }
1396 ;
1397
1398/* Value is number of statements counted as of the closeparen. */
1399simple_if:
1400 if_prefix lineno_labeled_stmt
1401/* Make sure expand_end_cond is run once
1402 for each call to expand_start_cond.
1403 Otherwise a crash is likely. */
1404 | if_prefix error
1405 ;
1406
1407if_prefix:
1408 IF '(' expr ')'
1409 { emit_line_note ($<filename>-1, $<lineno>0);
1410 expand_start_cond (truthvalue_conversion ($3), 0);
1411 $<itype>1 = stmt_count;
1412 if_stmt_file = $<filename>-1;
1413 if_stmt_line = $<lineno>0;
1414 position_after_white_space (); }
1415 ;
1416
1417/* This is a subroutine of stmt.
1418 It is used twice, once for valid DO statements
1419 and once for catching errors in parsing the end test. */
1420do_stmt_start:
1421 DO
1422 { stmt_count++;
1423 emit_line_note ($<filename>-1, $<lineno>0);
1424 /* See comment in `while' alternative, above. */
1425 emit_nop ();
1426 expand_start_loop_continue_elsewhere (1);
1427 position_after_white_space (); }
1428 lineno_labeled_stmt WHILE
1429 { expand_loop_continue_here (); }
1430 ;
1431
1432save_filename:
1433 { $$ = input_filename; }
1434 ;
1435
1436save_lineno:
1437 { $$ = lineno; }
1438 ;
1439
1440lineno_labeled_stmt:
1441 save_filename save_lineno stmt
1442 { }
1443/* | save_filename save_lineno error
1444 { }
1445*/
1446 | save_filename save_lineno label lineno_labeled_stmt
1447 { }
1448 ;
1449
1450lineno_stmt_or_label:
1451 save_filename save_lineno stmt_or_label
1452 { }
1453 ;
1454
1455stmt_or_label:
1456 stmt
1457 | label
1458 { int next;
1459 position_after_white_space ();
1460 next = getc (finput);
1461 ungetc (next, finput);
1462 if (pedantic && next == '}')
1463 pedwarn ("ANSI C forbids label at end of compound statement");
1464 }
1465 ;
1466
1467/* Parse a single real statement, not including any labels. */
1468stmt:
1469 compstmt
1470 { stmt_count++; }
1471 | expr ';'
1472 { stmt_count++;
1473 emit_line_note ($<filename>-1, $<lineno>0);
1474 c_expand_expr_stmt ($1);
1475 clear_momentary (); }
1476 | simple_if ELSE
1477 { expand_start_else ();
1478 $<itype>1 = stmt_count;
1479 position_after_white_space (); }
1480 lineno_labeled_stmt
1481 { expand_end_cond ();
1482 if (extra_warnings && stmt_count == $<itype>1)
1483 warning ("empty body in an else-statement"); }
1484 | simple_if %prec IF
1485 { expand_end_cond ();
1486 if (extra_warnings && stmt_count == $<itype>1)
1487 warning_with_file_and_line (if_stmt_file, if_stmt_line,
1488 "empty body in an if-statement"); }
1489/* Make sure expand_end_cond is run once
1490 for each call to expand_start_cond.
1491 Otherwise a crash is likely. */
1492 | simple_if ELSE error
1493 { expand_end_cond (); }
1494 | WHILE
1495 { stmt_count++;
1496 emit_line_note ($<filename>-1, $<lineno>0);
1497 /* The emit_nop used to come before emit_line_note,
1498 but that made the nop seem like part of the preceding line.
1499 And that was confusing when the preceding line was
1500 inside of an if statement and was not really executed.
1501 I think it ought to work to put the nop after the line number.
1502 We will see. --rms, July 15, 1991. */
1503 emit_nop (); }
1504 '(' expr ')'
1505 { /* Don't start the loop till we have succeeded
1506 in parsing the end test. This is to make sure
1507 that we end every loop we start. */
1508 expand_start_loop (1);
1509 emit_line_note (input_filename, lineno);
1510 expand_exit_loop_if_false (NULL_PTR,
1511 truthvalue_conversion ($4));
1512 position_after_white_space (); }
1513 lineno_labeled_stmt
1514 { expand_end_loop (); }
1515 | do_stmt_start
1516 '(' expr ')' ';'
1517 { emit_line_note (input_filename, lineno);
1518 expand_exit_loop_if_false (NULL_PTR,
1519 truthvalue_conversion ($3));
1520 expand_end_loop ();
1521 clear_momentary (); }
1522/* This rule is needed to make sure we end every loop we start. */
1523 | do_stmt_start error
1524 { expand_end_loop ();
1525 clear_momentary (); }
1526 | FOR
1527 '(' xexpr ';'
1528 { stmt_count++;
1529 emit_line_note ($<filename>-1, $<lineno>0);
1530 /* See comment in `while' alternative, above. */
1531 emit_nop ();
1532 if ($3) c_expand_expr_stmt ($3);
1533 /* Next step is to call expand_start_loop_continue_elsewhere,
1534 but wait till after we parse the entire for (...).
1535 Otherwise, invalid input might cause us to call that
1536 fn without calling expand_end_loop. */
1537 }
1538 xexpr ';'
1539 /* Can't emit now; wait till after expand_start_loop... */
1540 { $<lineno>7 = lineno;
1541 $<filename>$ = input_filename; }
1542 xexpr ')'
1543 {
1544 /* Start the loop. Doing this after parsing
1545 all the expressions ensures we will end the loop. */
1546 expand_start_loop_continue_elsewhere (1);
1547 /* Emit the end-test, with a line number. */
1548 emit_line_note ($<filename>8, $<lineno>7);
1549 if ($6)
1550 expand_exit_loop_if_false (NULL_PTR,
1551 truthvalue_conversion ($6));
1552 /* Don't let the tree nodes for $9 be discarded by
1553 clear_momentary during the parsing of the next stmt. */
1554 push_momentary ();
1555 $<lineno>7 = lineno;
1556 $<filename>8 = input_filename; }
1557 lineno_labeled_stmt
1558 { /* Emit the increment expression, with a line number. */
1559 emit_line_note ($<filename>8, $<lineno>7);
1560 expand_loop_continue_here ();
1561 if ($9)
1562 c_expand_expr_stmt ($9);
1563 pop_momentary ();
1564 expand_end_loop (); }
1565 | SWITCH '(' expr ')'
1566 { stmt_count++;
1567 emit_line_note ($<filename>-1, $<lineno>0);
1568 c_expand_start_case ($3);
1569 /* Don't let the tree nodes for $3 be discarded by
1570 clear_momentary during the parsing of the next stmt. */
1571 push_momentary ();
1572 position_after_white_space (); }
1573 lineno_labeled_stmt
1574 { expand_end_case ($3);
1575 pop_momentary (); }
1576 | BREAK ';'
1577 { stmt_count++;
1578 emit_line_note ($<filename>-1, $<lineno>0);
1579 if ( ! expand_exit_something ())
1580 error ("break statement not within loop or switch"); }
1581 | CONTINUE ';'
1582 { stmt_count++;
1583 emit_line_note ($<filename>-1, $<lineno>0);
1584 if (! expand_continue_loop (NULL_PTR))
1585 error ("continue statement not within a loop"); }
1586 | RETURN ';'
1587 { stmt_count++;
1588 emit_line_note ($<filename>-1, $<lineno>0);
1589 c_expand_return (NULL_TREE); }
1590 | RETURN expr ';'
1591 { stmt_count++;
1592 emit_line_note ($<filename>-1, $<lineno>0);
1593 c_expand_return ($2); }
1594 | ASM_KEYWORD maybe_type_qual '(' expr ')' ';'
1595 { stmt_count++;
1596 emit_line_note ($<filename>-1, $<lineno>0);
1597 STRIP_NOPS ($4);
1598 if ((TREE_CODE ($4) == ADDR_EXPR
1599 && TREE_CODE (TREE_OPERAND ($4, 0)) == STRING_CST)
1600 || TREE_CODE ($4) == STRING_CST)
1601 expand_asm ($4);
1602 else
1603 error ("argument of `asm' is not a constant string"); }
1604 /* This is the case with just output operands. */
1605 | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ')' ';'
1606 { stmt_count++;
1607 emit_line_note ($<filename>-1, $<lineno>0);
1608 c_expand_asm_operands ($4, $6, NULL_TREE, NULL_TREE,
1609 $2 == ridpointers[(int)RID_VOLATILE],
1610 input_filename, lineno); }
1611 /* This is the case with input operands as well. */
1612 | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':' asm_operands ')' ';'
1613 { stmt_count++;
1614 emit_line_note ($<filename>-1, $<lineno>0);
1615 c_expand_asm_operands ($4, $6, $8, NULL_TREE,
1616 $2 == ridpointers[(int)RID_VOLATILE],
1617 input_filename, lineno); }
1618 /* This is the case with clobbered registers as well. */
1619 | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
1620 asm_operands ':' asm_clobbers ')' ';'
1621 { stmt_count++;
1622 emit_line_note ($<filename>-1, $<lineno>0);
1623 c_expand_asm_operands ($4, $6, $8, $10,
1624 $2 == ridpointers[(int)RID_VOLATILE],
1625 input_filename, lineno); }
1626 | GOTO identifier ';'
1627 { tree decl;
1628 stmt_count++;
1629 emit_line_note ($<filename>-1, $<lineno>0);
1630 decl = lookup_label ($2);
1631 if (decl != 0)
1632 {
1633 TREE_USED (decl) = 1;
1634 expand_goto (decl);
1635 }
1636 }
1637 | GOTO '*' expr ';'
1638 { stmt_count++;
1639 emit_line_note ($<filename>-1, $<lineno>0);
1640 expand_computed_goto (convert (ptr_type_node, $3)); }
1641 | ';'
1642 ;
1643
1644/* Any kind of label, including jump labels and case labels.
1645 ANSI C accepts labels only before statements, but we allow them
1646 also at the end of a compound statement. */
1647
1648label: CASE expr ':'
1649 { register tree value = check_case_value ($2);
1650 register tree label
1651 = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
1652
1653 stmt_count++;
1654
1655 if (value != error_mark_node)
1656 {
1657 tree duplicate;
1658 int success = pushcase (value, label, &duplicate);
1659 if (success == 1)
1660 error ("case label not within a switch statement");
1661 else if (success == 2)
1662 {
1663 error ("duplicate case value");
1664 error_with_decl (duplicate, "this is the first entry for that value");
1665 }
1666 else if (success == 3)
1667 warning ("case value out of range");
1668 else if (success == 5)
1669 error ("case label within scope of cleanup or variable array");
1670 }
1671 position_after_white_space (); }
1672 | CASE expr ELLIPSIS expr ':'
1673 { register tree value1 = check_case_value ($2);
1674 register tree value2 = check_case_value ($4);
1675 register tree label
1676 = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
1677
1678 stmt_count++;
1679
1680 if (value1 != error_mark_node && value2 != error_mark_node)
1681 {
1682 tree duplicate;
1683 int success = pushcase_range (value1, value2, label,
1684 &duplicate);
1685 if (success == 1)
1686 error ("case label not within a switch statement");
1687 else if (success == 2)
1688 {
1689 error ("duplicate case value");
1690 error_with_decl (duplicate, "this is the first entry for that value");
1691 }
1692 else if (success == 3)
1693 warning ("case value out of range");
1694 else if (success == 4)
1695 warning ("empty case range");
1696 else if (success == 5)
1697 error ("case label within scope of cleanup or variable array");
1698 }
1699 position_after_white_space (); }
1700 | DEFAULT ':'
1701 {
1702 tree duplicate;
1703 register tree label
1704 = build_decl (LABEL_DECL, NULL_TREE, NULL_TREE);
1705 int success = pushcase (NULL_TREE, label, &duplicate);
1706 stmt_count++;
1707 if (success == 1)
1708 error ("default label not within a switch statement");
1709 else if (success == 2)
1710 {
1711 error ("multiple default labels in one switch");
1712 error_with_decl (duplicate, "this is the first default label");
1713 }
1714 position_after_white_space (); }
1715 | identifier ':'
1716 { tree label = define_label (input_filename, lineno, $1);
1717 stmt_count++;
1718 emit_nop ();
1719 if (label)
1720 expand_label (label);
1721 position_after_white_space (); }
1722 ;
1723
1724/* Either a type-qualifier or nothing. First thing in an `asm' statement. */
1725
1726maybe_type_qual:
1727 /* empty */
1728 { emit_line_note (input_filename, lineno); }
1729 | TYPE_QUAL
1730 { emit_line_note (input_filename, lineno); }
1731 ;
1732
1733xexpr:
1734 /* empty */
1735 { $$ = NULL_TREE; }
1736 | expr
1737 ;
1738
1739/* These are the operands other than the first string and colon
1740 in asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x)) */
1741asm_operands: /* empty */
1742 { $$ = NULL_TREE; }
1743 | nonnull_asm_operands
1744 ;
1745
1746nonnull_asm_operands:
1747 asm_operand
1748 | nonnull_asm_operands ',' asm_operand
1749 { $$ = chainon ($1, $3); }
1750 ;
1751
1752asm_operand:
1753 STRING '(' expr ')'
1754 { $$ = build_tree_list ($1, $3); }
1755 ;
1756
1757asm_clobbers:
1758 string
1759 { $$ = tree_cons (NULL_TREE, combine_strings ($1), NULL_TREE); }
1760 | asm_clobbers ',' string
1761 { $$ = tree_cons (NULL_TREE, combine_strings ($3), $1); }
1762 ;
1763\f
1764/* This is what appears inside the parens in a function declarator.
1765 Its value is a list of ..._TYPE nodes. */
1766parmlist:
1767 { pushlevel (0);
1768 clear_parm_order ();
1769 declare_parm_level (0); }
1770 parmlist_1
1771 { $$ = $2;
1772 parmlist_tags_warning ();
1773 poplevel (0, 0, 0); }
1774 ;
1775
1776parmlist_1:
1777 parmlist_2 ')'
1778 | parms ';'
1779 { tree parm;
1780 if (pedantic)
1781 pedwarn ("ANSI C forbids forward parameter declarations");
1782 /* Mark the forward decls as such. */
1783 for (parm = getdecls (); parm; parm = TREE_CHAIN (parm))
1784 TREE_ASM_WRITTEN (parm) = 1;
1785 clear_parm_order (); }
1786 parmlist_1
1787 { $$ = $4; }
1788 | error ')'
1789 { $$ = tree_cons (NULL_TREE, NULL_TREE, NULL_TREE); }
1790 ;
1791
1792/* This is what appears inside the parens in a function declarator.
1793 Is value is represented in the format that grokdeclarator expects. */
1794parmlist_2: /* empty */
1795 { $$ = get_parm_info (0); }
1796 | ELLIPSIS
1797 { $$ = get_parm_info (0);
1798 if (pedantic)
1799 pedwarn ("ANSI C requires a named argument before `...'");
1800 }
1801 | parms
1802 { $$ = get_parm_info (1); }
1803 | parms ',' ELLIPSIS
1804 { $$ = get_parm_info (0); }
1805 ;
1806
1807parms:
1808 parm
1809 { push_parm_decl ($1); }
1810 | parms ',' parm
1811 { push_parm_decl ($3); }
1812 ;
1813
1814/* A single parameter declaration or parameter type name,
1815 as found in a parmlist. */
1816parm:
1817 typed_declspecs parm_declarator
1818 { $$ = build_tree_list ($1, $2) ; }
1819 | typed_declspecs notype_declarator
1820 { $$ = build_tree_list ($1, $2) ; }
1821 | typed_declspecs absdcl
1822 { $$ = build_tree_list ($1, $2); }
1823 | declmods notype_declarator
1824 { $$ = build_tree_list ($1, $2) ; }
1825 | declmods absdcl
1826 { $$ = build_tree_list ($1, $2); }
1827 ;
1828
1829/* This is used in a function definition
1830 where either a parmlist or an identifier list is ok.
1831 Its value is a list of ..._TYPE nodes or a list of identifiers. */
1832parmlist_or_identifiers:
1833 { pushlevel (0);
1834 clear_parm_order ();
1835 declare_parm_level (1); }
1836 parmlist_or_identifiers_1
1837 { $$ = $2;
1838 parmlist_tags_warning ();
1839 poplevel (0, 0, 0); }
1840 ;
1841
1842parmlist_or_identifiers_1:
1843 parmlist_1
1844 | identifiers ')'
1845 { tree t;
1846 for (t = $1; t; t = TREE_CHAIN (t))
1847 if (TREE_VALUE (t) == NULL_TREE)
1848 error ("`...' in old-style identifier list");
1849 $$ = tree_cons (NULL_TREE, NULL_TREE, $1); }
1850 ;
1851
1852/* A nonempty list of identifiers. */
1853identifiers:
1854 IDENTIFIER
1855 { $$ = build_tree_list (NULL_TREE, $1); }
1856 | identifiers ',' IDENTIFIER
1857 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
1858 ;
1859
1860/* A nonempty list of identifiers, including typenames. */
1861identifiers_or_typenames:
1862 identifier
1863 { $$ = build_tree_list (NULL_TREE, $1); }
1864 | identifiers_or_typenames ',' identifier
1865 { $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
1866 ;
1867\f
1868/* Objective-C productions. */
1869
1870objcdef:
1871 classdef
1872 | methoddef
1873 | END
1874 {
1875 if (objc_implementation_context)
1876 {
1877 finish_class (objc_implementation_context);
1878 objc_ivar_chain = NULL_TREE;
1879 objc_implementation_context = NULL_TREE;
1880 }
1881 else
1882 warning ("`@end' must appear in an implementation context");
1883 }
1884 ;
1885
1886classdef:
1887 INTERFACE identifier '{'
1888 {
1889 objc_interface_context = objc_ivar_context
1890 = start_class (INTERFACE_TYPE, $2, NULL_TREE);
1891 objc_public_flag = 0;
1892 }
1893 ivar_decl_list '}'
1894 {
1895 continue_class (objc_interface_context);
1896 }
1897 methodprotolist
1898 END
1899 {
1900 finish_class (objc_interface_context);
1901 objc_interface_context = NULL_TREE;
1902 }
1903
1904 | INTERFACE identifier
1905 {
1906 objc_interface_context
1907 = start_class (INTERFACE_TYPE, $2, NULL_TREE);
1908 continue_class (objc_interface_context);
1909 }
1910 methodprotolist
1911 END
1912 {
1913 finish_class (objc_interface_context);
1914 objc_interface_context = NULL_TREE;
1915 }
1916
1917 | INTERFACE identifier ':' identifier '{'
1918 {
1919 objc_interface_context = objc_ivar_context
1920 = start_class (INTERFACE_TYPE, $2, $4);
1921 objc_public_flag = 0;
1922 }
1923 ivar_decl_list '}'
1924 {
1925 continue_class (objc_interface_context);
1926 }
1927 methodprotolist
1928 END
1929 {
1930 finish_class (objc_interface_context);
1931 objc_interface_context = NULL_TREE;
1932 }
1933
1934 | INTERFACE identifier ':' identifier
1935 {
1936 objc_interface_context
1937 = start_class (INTERFACE_TYPE, $2, $4);
1938 continue_class (objc_interface_context);
1939 }
1940 methodprotolist
1941 END
1942 {
1943 finish_class (objc_interface_context);
1944 objc_interface_context = NULL_TREE;
1945 }
1946
1947 | IMPLEMENTATION identifier '{'
1948 {
1949 objc_implementation_context = objc_ivar_context
1950 = start_class (IMPLEMENTATION_TYPE, $2, NULL_TREE);
1951 objc_public_flag = 0;
1952 }
1953 ivar_decl_list '}'
1954 {
1955 objc_ivar_chain
1956 = continue_class (objc_implementation_context);
1957 }
1958
1959 | IMPLEMENTATION identifier
1960 {
1961 objc_implementation_context
1962 = start_class (IMPLEMENTATION_TYPE, $2, NULL_TREE);
1963 objc_ivar_chain
1964 = continue_class (objc_implementation_context);
1965 }
1966
1967 | IMPLEMENTATION identifier ':' identifier '{'
1968 {
1969 objc_implementation_context = objc_ivar_context
1970 = start_class (IMPLEMENTATION_TYPE, $2, $4);
1971 objc_public_flag = 0;
1972 }
1973 ivar_decl_list '}'
1974 {
1975 objc_ivar_chain
1976 = continue_class (objc_implementation_context);
1977 }
1978
1979 | IMPLEMENTATION identifier ':' identifier
1980 {
1981 objc_implementation_context
1982 = start_class (IMPLEMENTATION_TYPE, $2, $4);
1983 objc_ivar_chain
1984 = continue_class (objc_implementation_context);
1985 }
1986
1987 | INTERFACE identifier '(' identifier ')'
1988 {
1989 objc_interface_context
1990 = start_class (PROTOCOL_TYPE, $2, $4);
1991 continue_class (objc_interface_context);
1992 }
1993 methodprotolist
1994 END
1995 {
1996 finish_class (objc_interface_context);
1997 objc_interface_context = NULL_TREE;
1998 }
1999
2000 | IMPLEMENTATION identifier '(' identifier ')'
2001 {
2002 objc_implementation_context
2003 = start_class (CATEGORY_TYPE, $2, $4);
2004 objc_ivar_chain
2005 = continue_class (objc_implementation_context);
2006 }
2007 ;
2008
2009ivar_decl_list:
2010 ivar_decls PUBLIC { objc_public_flag = 1; } ivar_decls
2011 | ivar_decls
2012 ;
2013
2014ivar_decls:
2015 /* empty */
2016 {
2017 $$ = NULL_TREE;
2018 }
2019 | ivar_decls ivar_decl ';'
2020 | ivar_decls ';'
2021 {
2022 if (pedantic)
2023 warning ("extra semicolon in struct or union specified");
2024 }
2025 ;
2026
2027
2028/* There is a shift-reduce conflict here, because `components' may
2029 start with a `typename'. It happens that shifting (the default resolution)
2030 does the right thing, because it treats the `typename' as part of
2031 a `typed_typespecs'.
2032
2033 It is possible that this same technique would allow the distinction
2034 between `notype_initdecls' and `initdecls' to be eliminated.
2035 But I am being cautious and not trying it. */
2036
2037ivar_decl:
2038 typed_typespecs setspecs ivars
2039 {
2040 $$ = $3;
2041 resume_momentary ($2);
2042 }
2043 | nonempty_type_quals setspecs ivars
2044 {
2045 $$ = $3;
2046 resume_momentary ($2);
2047 }
2048 | error
2049 { $$ = NULL_TREE; }
2050 ;
2051
2052ivars:
2053 /* empty */
2054 { $$ = NULL_TREE; }
2055 | ivar_declarator
2056 | ivars ',' ivar_declarator
2057 ;
2058
2059ivar_declarator:
2060 declarator
2061 {
2062 $$ = add_instance_variable (objc_ivar_context,
2063 objc_public_flag,
2064 $1, current_declspecs,
2065 NULL_TREE);
2066 }
2067 | declarator ':' expr_no_commas
2068 {
2069 $$ = add_instance_variable (objc_ivar_context,
2070 objc_public_flag,
2071 $1, current_declspecs, $3);
2072 }
2073 | ':' expr_no_commas
2074 {
2075 $$ = add_instance_variable (objc_ivar_context,
2076 objc_public_flag,
2077 NULL_TREE,
2078 current_declspecs, $2);
2079 }
2080 ;
2081
2082methoddef:
2083 '+'
2084 {
2085 if (objc_implementation_context)
2086 objc_inherit_code = CLASS_METHOD_DECL;
2087 else
2088 fatal ("method definition not in class context");
2089 }
2090 methoddecl
2091 {
2092 add_class_method (objc_implementation_context, $3);
2093 start_method_def ($3);
2094 objc_method_context = $3;
2095 }
2096 optarglist
2097 {
2098 continue_method_def ();
2099 }
2100 compstmt_or_error
2101 {
2102 finish_method_def ();
2103 objc_method_context = NULL_TREE;
2104 }
2105
2106 | '-'
2107 {
2108 if (objc_implementation_context)
2109 objc_inherit_code = INSTANCE_METHOD_DECL;
2110 else
2111 fatal ("method definition not in class context");
2112 }
2113 methoddecl
2114 {
2115 add_instance_method (objc_implementation_context, $3);
2116 start_method_def ($3);
2117 objc_method_context = $3;
2118 }
2119 optarglist
2120 {
2121 continue_method_def ();
2122 }
2123 compstmt_or_error
2124 {
2125 finish_method_def ();
2126 objc_method_context = NULL_TREE;
2127 }
2128 ;
2129
2130/* the reason for the strange actions in this rule
2131 is so that notype_initdecls when reached via datadef
2132 can find a valid list of type and sc specs in $0. */
2133
2134methodprotolist:
2135 /* empty */
2136 | {$<ttype>$ = NULL_TREE; } methodprotolist2
2137 ;
2138
2139methodprotolist2: /* eliminates a shift/reduce conflict */
2140 methodproto
2141 | datadef
2142 | methodprotolist2 methodproto
2143 | methodprotolist2 {$<ttype>$ = NULL_TREE; } datadef
2144 ;
2145
2146semi_or_error:
2147 ';'
2148 | error
2149 ;
2150
2151methodproto:
2152 '+'
2153 {
2154 objc_inherit_code = CLASS_METHOD_DECL;
2155 }
2156 methoddecl
2157 {
2158 add_class_method (objc_interface_context, $3);
2159 }
2160 semi_or_error
2161
2162 | '-'
2163 {
2164 objc_inherit_code = INSTANCE_METHOD_DECL;
2165 }
2166 methoddecl
2167 {
2168 add_instance_method (objc_interface_context, $3);
2169 }
2170 semi_or_error
2171 ;
2172
2173methoddecl:
2174 '(' typename ')' unaryselector
2175 {
2176 $$ = build_method_decl (objc_inherit_code, $2, $4, NULL_TREE);
2177 }
2178
2179 | unaryselector
2180 {
2181 $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, NULL_TREE);
2182 }
2183
2184 | '(' typename ')' keywordselector optparmlist
2185 {
2186 $$ = build_method_decl (objc_inherit_code, $2, $4, $5);
2187 }
2188
2189 | keywordselector optparmlist
2190 {
2191 $$ = build_method_decl (objc_inherit_code, NULL_TREE, $1, $2);
2192 }
2193 ;
2194
2195/* "optarglist" assumes that start_method_def has already been called...
2196 if it is not, the "xdecls" will not be placed in the proper scope */
2197
2198optarglist:
2199 /* empty */
2200 | ';' myxdecls
2201 ;
2202
2203/* to get around the following situation: "int foo (int a) int b; {}" that
2204 is synthesized when parsing "- a:a b:b; id c; id d; { ... }" */
2205
2206myxdecls:
2207 /* empty */
2208 | mydecls
2209 ;
2210
2211mydecls:
2212 mydecl
2213 | errstmt
2214 | mydecls mydecl
2215 | mydecl errstmt
2216 ;
2217
2218mydecl:
2219 typed_declspecs setspecs myparms ';'
2220 { resume_momentary ($2); }
2221 | typed_declspecs ';'
2222 { shadow_tag ($1); }
2223 | declmods ';'
2224 { pedwarn ("empty declaration"); }
2225 ;
2226
2227myparms:
2228 myparm
2229 { push_parm_decl ($1); }
2230 | myparms ',' myparm
2231 { push_parm_decl ($3); }
2232 ;
2233
2234/* A single parameter declaration or parameter type name,
2235 as found in a parmlist. DOES NOT ALLOW AN INITIALIZER OR ASMSPEC */
2236
2237myparm:
2238 parm_declarator
2239 { $$ = build_tree_list (current_declspecs, $1) ; }
2240 | notype_declarator
2241 { $$ = build_tree_list (current_declspecs, $1) ; }
2242 | absdcl
2243 { $$ = build_tree_list (current_declspecs, $1) ; }
2244 ;
2245
2246optparmlist:
2247 /* empty */
2248 {
2249 $$ = NULL_TREE;
2250 }
2251 | ',' ELLIPSIS
2252 {
2253 /* oh what a kludge! */
2254 $$ = (tree)1;
2255 }
2256 | ','
2257 {
2258 pushlevel (0);
2259 }
2260 parmlist_2
2261 {
2262 /* returns a tree list node generated by get_parm_info */
2263 $$ = $3;
2264 poplevel (0, 0, 0);
2265 }
2266 ;
2267
2268unaryselector:
2269 selector
2270 ;
2271
2272keywordselector:
2273 keyworddecl
2274
2275 | keywordselector keyworddecl
2276 {
2277 $$ = chainon ($1, $2);
2278 }
2279 ;
2280
2281selector:
2282 IDENTIFIER
2283 | TYPENAME
2284 | reservedwords
2285 ;
2286
2287reservedwords:
2288 ENUM { $$ = get_identifier (token_buffer); }
2289 | STRUCT { $$ = get_identifier (token_buffer); }
2290 | UNION { $$ = get_identifier (token_buffer); }
2291 | IF { $$ = get_identifier (token_buffer); }
2292 | ELSE { $$ = get_identifier (token_buffer); }
2293 | WHILE { $$ = get_identifier (token_buffer); }
2294 | DO { $$ = get_identifier (token_buffer); }
2295 | FOR { $$ = get_identifier (token_buffer); }
2296 | SWITCH { $$ = get_identifier (token_buffer); }
2297 | CASE { $$ = get_identifier (token_buffer); }
2298 | DEFAULT { $$ = get_identifier (token_buffer); }
2299 | BREAK { $$ = get_identifier (token_buffer); }
2300 | CONTINUE { $$ = get_identifier (token_buffer); }
2301 | RETURN { $$ = get_identifier (token_buffer); }
2302 | GOTO { $$ = get_identifier (token_buffer); }
2303 | ASM_KEYWORD { $$ = get_identifier (token_buffer); }
2304 | SIZEOF { $$ = get_identifier (token_buffer); }
2305 | TYPEOF { $$ = get_identifier (token_buffer); }
2306 | ALIGNOF { $$ = get_identifier (token_buffer); }
2307 | TYPESPEC | TYPE_QUAL
2308 ;
2309
2310keyworddecl:
2311 selector ':' '(' typename ')' identifier
2312 {
2313 $$ = build_keyword_decl ($1, $4, $6);
2314 }
2315
2316 | selector ':' identifier
2317 {
2318 $$ = build_keyword_decl ($1, NULL_TREE, $3);
2319 }
2320
2321 | ':' '(' typename ')' identifier
2322 {
2323 $$ = build_keyword_decl (NULL_TREE, $3, $5);
2324 }
2325
2326 | ':' identifier
2327 {
2328 $$ = build_keyword_decl (NULL_TREE, NULL_TREE, $2);
2329 }
2330 ;
2331
2332messageargs:
2333 selector
2334 | keywordarglist
2335 ;
2336
2337keywordarglist:
2338 keywordarg
2339 | keywordarglist keywordarg
2340 {
2341 $$ = chainon ($1, $2);
2342 }
2343 ;
2344
2345
2346keywordexpr:
2347 nonnull_exprlist
2348 {
2349 if (TREE_CHAIN ($1) == NULL_TREE)
2350 /* just return the expr., remove a level of indirection */
2351 $$ = TREE_VALUE ($1);
2352 else
2353 /* we have a comma expr., we will collapse later */
2354 $$ = $1;
2355 }
2356 ;
2357
2358keywordarg:
2359 selector ':' keywordexpr
2360 {
2361 $$ = build_tree_list ($1, $3);
2362 }
2363 | ':' keywordexpr
2364 {
2365 $$ = build_tree_list (NULL_TREE, $2);
2366 }
2367 ;
2368
2369receiver:
2370 expr
2371 | CLASSNAME
2372 {
2373 $$ = get_class_reference ($1);
2374 }
2375 ;
2376
2377objcmessageexpr:
2378 '['
2379 { objc_receiver_context = 1; }
2380 receiver
2381 { objc_receiver_context = 0; }
2382 messageargs ']'
2383 {
2384 $$ = build_tree_list ($3, $5);
2385 }
2386 ;
2387
2388selectorarg:
2389 selector
2390 | keywordnamelist
2391 ;
2392
2393keywordnamelist:
2394 keywordname
2395 | keywordnamelist keywordname
2396 {
2397 $$ = chainon ($1, $2);
2398 }
2399 ;
2400
2401keywordname:
2402 selector ':'
2403 {
2404 $$ = build_tree_list ($1, NULL_TREE);
2405 }
2406 | ':'
2407 {
2408 $$ = build_tree_list (NULL_TREE, NULL_TREE);
2409 }
2410 ;
2411
2412objcselectorexpr:
2413 SELECTOR '(' selectorarg ')'
2414 {
2415 $$ = $3;
2416 }
2417 ;
2418
2419/* extension to support C-structures in the archiver */
2420
2421objcencodeexpr:
2422 ENCODE '(' typename ')'
2423 {
2424 $$ = groktypename ($3);
2425 }
2426 ;
2427
2428%%
2429
2430/* If STRING is the name of an Objective C @-keyword
2431 (not including the @), return the token type for that keyword.
2432 Otherwise return 0. */
2433
2434int
2435recognize_objc_keyword (string)
2436 char *string;
2437{
2438 switch (string[0])
2439 {
2440 case 'd':
2441 if (!strcmp (string, "defs"))
2442 return DEFS;
2443 break;
2444 case 'e':
2445 if (!strcmp (string, "end"))
2446 return END;
2447 if (!strcmp (string, "encode"))
2448 return ENCODE;
2449 break;
2450 case 'i':
2451 if (!strcmp (string, "interface"))
2452 return INTERFACE;
2453 if (!strcmp (string, "implementation"))
2454 return IMPLEMENTATION;
2455 break;
2456 case 'p':
2457 if (!strcmp (string, "public"))
2458 return PUBLIC;
2459 break;
2460 case 's':
2461 if (!strcmp (string, "selector"))
2462 return SELECTOR;
2463 break;
2464 }
2465 return 0;
2466}
2467