blob: abf025d3a85f2c4187f2d6d9cb6ad75cf6948826 [file] [log] [blame]
/* YACC parser for C syntax and for Objective C. -*-c-*-
Copyright (C) 1987, 1988, 1989, 1992, 1993, 1994, 1995, 1996, 1997, 1998,
1999, 2000, 2001, 2002, 2003, 2004, 2005 Free Software Foundation, Inc.
This file is part of GCC.
GCC is free software; you can redistribute it and/or modify it under
the terms of the GNU General Public License as published by the Free
Software Foundation; either version 2, or (at your option) any later
version.
GCC is distributed in the hope that it will be useful, but WITHOUT ANY
WARRANTY; without even the implied warranty of MERCHANTABILITY or
FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License
for more details.
You should have received a copy of the GNU General Public License
along with GCC; see the file COPYING. If not, write to the Free
Software Foundation, 59 Temple Place - Suite 330, Boston, MA
02111-1307, USA. */
/* This file defines the grammar of C and that of Objective C.
@@ifobjc ... @@end_ifobjc conditionals contain code for Objective C only.
@@ifc ... @@end_ifc conditionals contain code for C only.
Sed commands in Makefile.in are used to convert this file into
c-parse.y and into objc-parse.y. */
/* To whomever it may concern: I have heard that such a thing was once
written by AT&T, but I have never seen it. */
@@ifc
/* APPLE LOCAL CW asm blocks */
%expect 16 /* shift/reduce conflicts, and no reduce/reduce conflicts. */
@@end_ifc
%{
#include "config.h"
#include "system.h"
#include "coretypes.h"
#include "tm.h"
#include "tree.h"
#include "langhooks.h"
#include "input.h"
#include "cpplib.h"
#include "intl.h"
#include "timevar.h"
#include "c-pragma.h" /* For YYDEBUG definition, and parse_in. */
#include "c-tree.h"
#include "flags.h"
#include "varray.h"
#include "output.h"
#include "toplev.h"
#include "ggc.h"
#include "c-common.h"
#define YYERROR1 { yyerror ("syntax error"); YYERROR; }
/* Like the default stack expander, except (1) use realloc when possible,
(2) impose no hard maxiumum on stack size, (3) REALLY do not use alloca.
Irritatingly, YYSTYPE is defined after this %{ %} block, so we cannot
give malloced_yyvs its proper type. This is ok since all we need from
it is to be able to free it. */
static short *malloced_yyss;
static void *malloced_yyvs;
#define yyoverflow(MSG, SS, SSSIZE, VS, VSSIZE, YYSSZ) \
do { \
size_t newsize; \
short *newss; \
YYSTYPE *newvs; \
newsize = *(YYSSZ) *= 2; \
if (malloced_yyss) \
{ \
newss = really_call_realloc (*(SS), newsize * sizeof (short)); \
newvs = really_call_realloc (*(VS), newsize * sizeof (YYSTYPE)); \
} \
else \
{ \
newss = really_call_malloc (newsize * sizeof (short)); \
newvs = really_call_malloc (newsize * sizeof (YYSTYPE)); \
if (newss) \
memcpy (newss, *(SS), (SSSIZE)); \
if (newvs) \
memcpy (newvs, *(VS), (VSSIZE)); \
} \
if (!newss || !newvs) \
{ \
yyerror (MSG); \
return 2; \
} \
*(SS) = newss; \
*(VS) = newvs; \
malloced_yyss = newss; \
malloced_yyvs = (void *) newvs; \
} while (0)
%}
%start program
%union {long itype; tree ttype; void *otype; struct c_expr exprtype;
struct c_arg_info *arginfotype; struct c_declarator *dtrtype;
struct c_type_name *typenametype; struct c_parm *parmtype;
struct c_declspecs *dsptype; struct c_typespec tstype;
enum tree_code code; location_t location; }
/* All identifiers that are not reserved words
and are not declared typedefs in the current block */
%token IDENTIFIER
/* All identifiers that are declared typedefs in the current block.
In some contexts, they are treated just like IDENTIFIER,
but they can also serve as typespecs in declarations. */
%token TYPENAME
/* Reserved words that specify storage class.
yylval contains an IDENTIFIER_NODE which indicates which one. */
%token SCSPEC /* Storage class other than static. */
%token STATIC /* Static storage class. */
/* Reserved words that specify type.
yylval contains an IDENTIFIER_NODE which indicates which one. */
%token TYPESPEC
/* Reserved words that qualify type: "const", "volatile", or "restrict".
yylval contains an IDENTIFIER_NODE which indicates which one. */
%token TYPE_QUAL
/* Objective-C protocol qualifiers. These acquire their magic powers
only in certain contexts. */
%token OBJC_TYPE_QUAL
/* Character or numeric constants.
yylval is the node for the constant. */
%token CONSTANT
/* String constants in raw form.
yylval is a STRING_CST node. */
%token STRING
/* "...", used for functions with variable arglists. */
%token ELLIPSIS
/* the reserved words */
/* SCO include files test "ASM", so use something else. */
%token SIZEOF ENUM STRUCT UNION IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
%token BREAK CONTINUE RETURN GOTO ASM_KEYWORD TYPEOF ALIGNOF
%token ATTRIBUTE EXTENSION LABEL
%token REALPART IMAGPART VA_ARG CHOOSE_EXPR TYPES_COMPATIBLE_P
%token FUNC_NAME OFFSETOF
/* APPLE LOCAL begin CW asm blocks (in 4.2 ac) */
/* This token is a pseudo-storage-class. */
%token IASM_ASM_KEYWORD
%type <ttype> IASM_ASM_KEYWORD
/* These tokens indicate beginning and end of each asm line. */
%token IASM_BOL IASM_EOL
/* APPLE LOCAL end CW asm blocks (in 4.2 ac) */
/* Add precedence rules to solve dangling else s/r conflict */
%nonassoc IF
%nonassoc ELSE
/* Define the operator tokens and their precedences.
The value is an integer because, if used, it is the tree code
to use in the expression made from the operator. */
%right <code> ASSIGN '='
%right <code> '?' ':'
%left <code> OROR
%left <code> ANDAND
%left <code> '|'
%left <code> '^'
%left <code> '&'
%left <code> EQCOMPARE
%left <code> ARITHCOMPARE
%left <code> LSHIFT RSHIFT
%left <code> '+' '-'
%left <code> '*' '/' '%'
%right <code> UNARY PLUSPLUS MINUSMINUS
%left HYPERUNARY
%left <code> POINTSAT '.' '(' '['
/* The Objective-C keywords. These are included in C and in
Objective C, so that the token codes are the same in both. */
%token AT_INTERFACE AT_IMPLEMENTATION AT_END AT_SELECTOR AT_DEFS AT_ENCODE
%token CLASSNAME AT_PUBLIC AT_PRIVATE AT_PROTECTED AT_PROTOCOL
%token AT_CLASS AT_ALIAS
%token AT_THROW AT_TRY AT_CATCH AT_FINALLY AT_SYNCHRONIZED
%token OBJC_STRING
/* APPLE LOCAL begin C* language (in 4.2 not needed) */
%token AT_IN AT_OPTIONAL AT_REQUIRED
/* APPLE LOCAL end C* language (in 4.2 not needed) */
/* APPLE LOCAL begin C* property (Radar 4436866, 4591909, 4621020) (in 4.2 not needed, except for 4591909, 4621020) */
%token AT_PROPERTY AT_READONLY AT_PROP_BYCOPY AT_GETTER AT_SETTER AT_IVAR
%token AT_PROP_BYREF AT_PROP_DYNAMIC AT_WEAK
/* APPLE LOCAL end C* property (Radar 4436866, 4591909, 4621020) (in 4.2 not needed, except for 4591909, 4621020) */
/* APPLE LOCAL objc new property */
%token AT_SYNTHESIZE AT_DYNAMIC AT_READWRITE AT_ASSIGN AT_RETAIN AT_COPY
/* APPLE LOCAL radar 4947014 - objc atomic property */
%token AT_NONATOMIC
/* APPLE LOCAL radar 4564694 */
%token AT_PACKAGE
%type <code> unop
%type <ttype> ENUM STRUCT UNION IF ELSE WHILE DO FOR SWITCH CASE DEFAULT
%type <ttype> BREAK CONTINUE RETURN GOTO ASM_KEYWORD SIZEOF TYPEOF ALIGNOF
%type <ttype> identifier IDENTIFIER TYPENAME CONSTANT STRING FUNC_NAME
%type <ttype> nonnull_exprlist exprlist
%type <exprtype> expr expr_no_commas cast_expr unary_expr primary
%type <dsptype> declspecs_nosc_nots_nosa_noea declspecs_nosc_nots_nosa_ea
%type <dsptype> declspecs_nosc_nots_sa_noea declspecs_nosc_nots_sa_ea
%type <dsptype> declspecs_nosc_ts_nosa_noea declspecs_nosc_ts_nosa_ea
%type <dsptype> declspecs_nosc_ts_sa_noea declspecs_nosc_ts_sa_ea
%type <dsptype> declspecs_sc_nots_nosa_noea declspecs_sc_nots_nosa_ea
%type <dsptype> declspecs_sc_nots_sa_noea declspecs_sc_nots_sa_ea
%type <dsptype> declspecs_sc_ts_nosa_noea declspecs_sc_ts_nosa_ea
%type <dsptype> declspecs_sc_ts_sa_noea declspecs_sc_ts_sa_ea
%type <dsptype> declspecs_ts declspecs_nots
%type <dsptype> declspecs_ts_nosa declspecs_nots_nosa
%type <dsptype> declspecs_nosc_ts declspecs_nosc_nots declspecs_nosc declspecs
%type <dsptype> maybe_type_quals_attrs
%type <tstype> typespec_nonattr typespec_attr
%type <tstype> typespec_reserved_nonattr typespec_reserved_attr
%type <tstype> typespec_nonreserved_nonattr
%type <ttype> offsetof_member_designator
%type <ttype> scspec SCSPEC STATIC TYPESPEC TYPE_QUAL maybe_volatile
%type <ttype> initdecls notype_initdecls initdcl notype_initdcl
%type <exprtype> init
%type <ttype> simple_asm_expr maybeasm asm_stmt asm_argument asm_string
%type <ttype> asm_operands nonnull_asm_operands asm_operand asm_clobbers
%type <ttype> maybe_attribute attributes attribute attribute_list attrib
%type <ttype> any_word
%type <ttype> compstmt compstmt_start compstmt_primary_start
%type <ttype> stmt label stmt_nocomp start_break start_continue
%type <ttype> c99_block_start c99_block_lineno_labeled_stmt
%type <ttype> if_statement_1 if_statement_2
%type <dtrtype> declarator
%type <dtrtype> notype_declarator after_type_declarator
%type <dtrtype> parm_declarator
%type <dtrtype> parm_declarator_starttypename parm_declarator_nostarttypename
%type <dtrtype> array_declarator
%type <tstype> structsp_attr structsp_nonattr
%type <ttype> component_decl_list component_decl_list2
%type <ttype> component_decl components components_notype component_declarator
%type <ttype> component_notype_declarator
%type <ttype> enumlist enumerator
%type <ttype> struct_head union_head enum_head
%type <typenametype> typename
%type <dtrtype> absdcl absdcl1 absdcl1_ea absdcl1_noea direct_absdcl1
%type <parmtype> absdcl_maybe_attribute
%type <ttype> condition xexpr for_cond_expr for_incr_expr
%type <parmtype> parm firstparm
%type <ttype> identifiers
%type <arginfotype> parms parmlist parmlist_1 parmlist_2
%type <arginfotype> parmlist_or_identifiers parmlist_or_identifiers_1
%type <ttype> identifiers_or_typenames
/* APPLE LOCAL begin CW asm blocks */
%type <ttype> iasm_identifier iasm_identifier1 iasm_maybe_prefix
%type <exprtype> iasm_expr_no_commas iasm_unary_expr
%type <exprtype> iasm_primary
%type <ttype> iasm_operands iasm_nonnull_operands
%type <exprtype> iasm_operand
%type <ttype> iasm_stmt iasm_stmt_nobol single_iasm_stmt
%type <ttype> iasm_compstmt iasm_compstmt_start
/* iasm_compstmt_nostart */
/* APPLE LOCAL end CW asm blocks */
%type <itype> setspecs setspecs_fp extension
%type <location> save_location
%type <otype> save_obstack_position
@@ifobjc
/* the Objective-C nonterminals */
%type <ttype> methoddecl unaryselector keywordselector selector
%type <code> methodtype
%type <ttype> keyworddecl receiver objcmessageexpr messageargs
%type <ttype> keywordexpr keywordarglist keywordarg
%type <ttype> optparmlist optparms reservedwords objcselectorexpr
%type <ttype> selectorarg keywordnamelist keywordname objcencodeexpr
%type <ttype> non_empty_protocolrefs protocolrefs identifier_list objcprotocolexpr
/* APPLE LOCAL C* language */
%type <ttype> for_objc_collection
/* APPLE LOCAL objc new property */
%type <ttype> property_synthesize_item property_synthesize_list property_implementation
%type <ttype> CLASSNAME OBJC_STRING OBJC_TYPE_QUAL
%type <ttype> superclass objc_quals objc_qual objc_typename
%type <itype> objc_try_catch_stmt optellipsis
/* APPLE LOCAL radar 2848255 */
%type <parmtype> objc_catch_parm
/* APPLE LOCAL radar 4965989 */
%type <ttype> optidentifier
@@end_ifobjc
%{
/* Declaration specifiers of the current declaration. */
static struct c_declspecs *current_declspecs;
static GTY(()) tree prefix_attributes;
/* List of all the attributes applying to the identifier currently being
declared; includes prefix_attributes and possibly some more attributes
just after a comma. */
static GTY(()) tree all_prefix_attributes;
/* Structure to save declaration specifiers. */
struct c_declspec_stack {
/* Saved value of current_declspecs. */
struct c_declspecs *current_declspecs;
/* Saved value of prefix_attributes. */
tree prefix_attributes;
/* Saved value of all_prefix_attributes. */
tree all_prefix_attributes;
/* Next level of stack. */
struct c_declspec_stack *next;
};
/* Stack of saved values of current_declspecs, prefix_attributes and
all_prefix_attributes. */
static struct c_declspec_stack *declspec_stack;
/* INDIRECT_REF with a TREE_TYPE of the type being queried for offsetof. */
static tree offsetof_base;
/* PUSH_DECLSPEC_STACK is called from setspecs; POP_DECLSPEC_STACK
should be called from the productions making use of setspecs. */
#define PUSH_DECLSPEC_STACK \
do { \
struct c_declspec_stack *t = XOBNEW (&parser_obstack, \
struct c_declspec_stack); \
t->current_declspecs = current_declspecs; \
t->prefix_attributes = prefix_attributes; \
t->all_prefix_attributes = all_prefix_attributes; \
t->next = declspec_stack; \
declspec_stack = t; \
} while (0)
#define POP_DECLSPEC_STACK \
do { \
current_declspecs = declspec_stack->current_declspecs; \
prefix_attributes = declspec_stack->prefix_attributes; \
all_prefix_attributes = declspec_stack->all_prefix_attributes; \
declspec_stack = declspec_stack->next; \
} while (0)
/* For __extension__, save/restore the warning flags which are
controlled by __extension__. */
#define SAVE_EXT_FLAGS() \
(pedantic \
| (warn_pointer_arith << 1) \
| (warn_traditional << 2) \
| (flag_iso << 3))
#define RESTORE_EXT_FLAGS(val) \
do { \
pedantic = val & 1; \
warn_pointer_arith = (val >> 1) & 1; \
warn_traditional = (val >> 2) & 1; \
flag_iso = (val >> 3) & 1; \
} while (0)
@@ifobjc
/* Objective-C specific parser/lexer information */
static int objc_pq_context = 0;
/* The following flag is needed to contextualize ObjC lexical analysis.
In some cases (e.g., 'int NSObject;'), it is undesirable to bind
an identifier to an ObjC class, even if a class with that name
exists. */
static int objc_need_raw_identifier;
#define OBJC_NEED_RAW_IDENTIFIER(VAL) objc_need_raw_identifier = VAL
/* APPLE LOCAL begin C* property (Radar 4436866) (in 4.2 d) */
/* For checking property attribute keywords */
static int objc_property_attr_context = 0;
/* APPLE LOCAL end C* property (Radar 4436866) (in 4.2 d) */
/* APPLE LOCAL radar 3803157 - objc attribute (in 4.2 e) */
static tree objc_method_attributes = NULL_TREE;
@@end_ifobjc
@@ifc
#define OBJC_NEED_RAW_IDENTIFIER(VAL) /* nothing */
@@end_ifc
/* Tell yyparse how to print a token's value, if yydebug is set. */
#define YYPRINT(FILE,YYCHAR,YYLVAL) yyprint(FILE,YYCHAR,YYLVAL)
/* APPLE LOCAL begin C* language (in 4.2 f) */
/* For checking for 'foreach' context. */
static int objc_foreach_context = 0;
/* APPLE LOCAL end C* language (in 4.2 f) */
static void yyprint (FILE *, int, YYSTYPE);
static void yyerror (const char *);
static int yylexname (void);
static inline int _yylex (void);
static int yylex (void);
static void init_reswords (void);
/* APPLE LOCAL begin CW asm blocks (in 4.2 g) */
static int iasm_lineno = 0;
#ifndef IASM_SEE_OPCODE
#define IASM_SEE_OPCODE(YYCHAR, T) YYCHAR
#endif
static tree c_parse_iasm_maybe_prefix (tree id);
/* APPLE LOCAL end CW asm blocks (in 4.2 g) */
/* Initialization routine for this file. */
void
c_parse_init (void)
{
init_reswords ();
}
%}
%%
program: /* empty */
{ if (pedantic)
pedwarn ("ISO C forbids an empty source file");
}
| extdefs
;
/* the reason for the strange actions in this rule
is so that notype_initdecls when reached via datadef
can find valid declaration specifiers in $0. */
extdefs:
save_obstack_position { $<dsptype>$ = NULL; } extdef
{ obstack_free (&parser_obstack, $1); }
| extdefs save_obstack_position
{ $<dsptype>$ = NULL; ggc_collect (); } extdef
{ obstack_free (&parser_obstack, $2); }
;
extdef:
fndef
| datadef
| asmdef
| extension extdef
{ RESTORE_EXT_FLAGS ($1); }
@@ifobjc
| objcdef
@@end_ifobjc
;
/* Record the current position of parser_obstack before a
declaration to restore it afterwards. */
save_obstack_position:
{ $$ = obstack_alloc (&parser_obstack, 0); }
;
datadef:
setspecs notype_initdecls ';'
{ pedwarn ("data definition has no type or storage class");
POP_DECLSPEC_STACK; }
| declspecs_nots setspecs notype_initdecls ';'
{ POP_DECLSPEC_STACK; }
| declspecs_ts setspecs initdecls ';'
{ POP_DECLSPEC_STACK; }
| declspecs ';'
{ shadow_tag (finish_declspecs ($1)); }
| error ';'
| error '}'
| ';'
{ if (pedantic)
pedwarn ("ISO C does not allow extra %<;%> outside of a function"); }
;
fndef:
declspecs_ts setspecs declarator
{ if (!start_function (current_declspecs, $3,
all_prefix_attributes))
YYERROR1;
}
old_style_parm_decls save_location
{ DECL_SOURCE_LOCATION (current_function_decl) = $6;
store_parm_decls (); }
compstmt_or_error
{ finish_function ();
POP_DECLSPEC_STACK; }
| declspecs_ts setspecs declarator error
{ POP_DECLSPEC_STACK; }
| declspecs_nots setspecs notype_declarator
{ if (!start_function (current_declspecs, $3,
all_prefix_attributes))
YYERROR1;
}
old_style_parm_decls save_location
{ DECL_SOURCE_LOCATION (current_function_decl) = $6;
store_parm_decls (); }
compstmt_or_error
{ finish_function ();
POP_DECLSPEC_STACK; }
| declspecs_nots setspecs notype_declarator error
{ POP_DECLSPEC_STACK; }
| setspecs notype_declarator
{ if (!start_function (current_declspecs, $2,
all_prefix_attributes))
YYERROR1;
}
old_style_parm_decls save_location
{ DECL_SOURCE_LOCATION (current_function_decl) = $5;
store_parm_decls (); }
compstmt_or_error
{ finish_function ();
POP_DECLSPEC_STACK; }
| setspecs notype_declarator error
{ POP_DECLSPEC_STACK; }
;
identifier:
IDENTIFIER
| TYPENAME
@@ifobjc
| CLASSNAME
@@end_ifobjc
;
unop: '&'
{ $$ = ADDR_EXPR; }
| '-'
{ $$ = NEGATE_EXPR; }
| '+'
{ $$ = CONVERT_EXPR;
@@ifc
if (warn_traditional && !in_system_header)
warning ("traditional C rejects the unary plus operator");
@@end_ifc
}
| PLUSPLUS
{ $$ = PREINCREMENT_EXPR; }
| MINUSMINUS
{ $$ = PREDECREMENT_EXPR; }
| '~'
{ $$ = BIT_NOT_EXPR; }
| '!'
{ $$ = TRUTH_NOT_EXPR; }
;
expr: expr_no_commas
| expr ',' expr_no_commas
{ $$.value = build_compound_expr ($1.value, $3.value);
$$.original_code = COMPOUND_EXPR; }
;
exprlist:
/* empty */
{ $$ = NULL_TREE; }
| nonnull_exprlist
;
nonnull_exprlist:
expr_no_commas
{ $$ = build_tree_list (NULL_TREE, $1.value); }
| nonnull_exprlist ',' expr_no_commas
{ chainon ($1, build_tree_list (NULL_TREE, $3.value)); }
;
unary_expr:
primary
| '*' cast_expr %prec UNARY
{ $$.value = build_indirect_ref ($2.value, "unary *");
$$.original_code = ERROR_MARK; }
/* __extension__ turns off -pedantic for following primary. */
| extension cast_expr %prec UNARY
{ $$ = $2;
RESTORE_EXT_FLAGS ($1); }
| unop cast_expr %prec UNARY
{ $$.value = build_unary_op ($1, $2.value, 0);
overflow_warning ($$.value);
$$.original_code = ERROR_MARK; }
/* Refer to the address of a label as a pointer. */
| ANDAND identifier
{ $$.value = finish_label_address_expr ($2);
$$.original_code = ERROR_MARK; }
| sizeof unary_expr %prec UNARY
{ skip_evaluation--;
in_sizeof--;
if (TREE_CODE ($2.value) == COMPONENT_REF
&& DECL_C_BIT_FIELD (TREE_OPERAND ($2.value, 1)))
error ("%<sizeof%> applied to a bit-field");
$$ = c_expr_sizeof_expr ($2); }
| sizeof '(' typename ')' %prec HYPERUNARY
{ skip_evaluation--;
in_sizeof--;
/* APPLE LOCAL begin mainline 2006-05-18 4336222 */
if ($3->declarator->kind == cdk_array
&& $3->declarator->u.array.vla_unspec_p)
{
/* C99 6.7.5.2p4 */
error ("%<[*]%> not allowed in other than a declaration");
}
/* APPLE LOCAL end mainline 2006-05-18 4336222 */
$$ = c_expr_sizeof_type ($3); }
| alignof unary_expr %prec UNARY
{ skip_evaluation--;
in_alignof--;
$$.value = c_alignof_expr ($2.value);
$$.original_code = ERROR_MARK; }
| alignof '(' typename ')' %prec HYPERUNARY
{ skip_evaluation--;
in_alignof--;
$$.value = c_alignof (groktypename ($3));
$$.original_code = ERROR_MARK; }
| REALPART cast_expr %prec UNARY
{ $$.value = build_unary_op (REALPART_EXPR, $2.value, 0);
$$.original_code = ERROR_MARK; }
| IMAGPART cast_expr %prec UNARY
{ $$.value = build_unary_op (IMAGPART_EXPR, $2.value, 0);
$$.original_code = ERROR_MARK; }
;
sizeof:
SIZEOF { skip_evaluation++; in_sizeof++; }
;
alignof:
ALIGNOF { skip_evaluation++; in_alignof++; }
;
typeof:
TYPEOF { skip_evaluation++; in_typeof++; }
;
cast_expr:
unary_expr
| '(' typename ')' cast_expr %prec UNARY
{ $$.value = c_cast_expr ($2, $4.value);
$$.original_code = ERROR_MARK; }
;
expr_no_commas:
/* APPLE LOCAL begin radar 4426814 */
cast_expr
{
if (c_dialect_objc() && flag_objc_gc)
$$.value = objc_generate_weak_read ($1.value); }
/* APPLE LOCAL end radar 4426814 */
| expr_no_commas '+' expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas '-' expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas '*' expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas '/' expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas '%' expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas LSHIFT expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas RSHIFT expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas ARITHCOMPARE expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas EQCOMPARE expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas '&' expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas '|' expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas '^' expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| expr_no_commas ANDAND
{ $1.value = lang_hooks.truthvalue_conversion
(default_conversion ($1.value));
skip_evaluation += $1.value == truthvalue_false_node; }
expr_no_commas
{ skip_evaluation -= $1.value == truthvalue_false_node;
$$ = parser_build_binary_op (TRUTH_ANDIF_EXPR, $1, $4); }
| expr_no_commas OROR
{ $1.value = lang_hooks.truthvalue_conversion
(default_conversion ($1.value));
skip_evaluation += $1.value == truthvalue_true_node; }
expr_no_commas
{ skip_evaluation -= $1.value == truthvalue_true_node;
$$ = parser_build_binary_op (TRUTH_ORIF_EXPR, $1, $4); }
| expr_no_commas '?'
{ $1.value = lang_hooks.truthvalue_conversion
(default_conversion ($1.value));
skip_evaluation += $1.value == truthvalue_false_node; }
expr ':'
{ skip_evaluation += (($1.value == truthvalue_true_node)
- ($1.value == truthvalue_false_node)); }
expr_no_commas
{ skip_evaluation -= $1.value == truthvalue_true_node;
$$.value = build_conditional_expr ($1.value, $4.value,
$7.value);
$$.original_code = ERROR_MARK; }
| expr_no_commas '?'
{ if (pedantic)
pedwarn ("ISO C forbids omitting the middle term of a ?: expression");
/* Make sure first operand is calculated only once. */
$<ttype>2 = save_expr (default_conversion ($1.value));
$1.value = lang_hooks.truthvalue_conversion ($<ttype>2);
skip_evaluation += $1.value == truthvalue_true_node; }
':' expr_no_commas
{ skip_evaluation -= $1.value == truthvalue_true_node;
$$.value = build_conditional_expr ($1.value, $<ttype>2,
$5.value);
$$.original_code = ERROR_MARK; }
| expr_no_commas '=' expr_no_commas
{ $$.value = build_modify_expr ($1.value, NOP_EXPR, $3.value);
$$.original_code = MODIFY_EXPR;
}
| expr_no_commas ASSIGN expr_no_commas
{ $$.value = build_modify_expr ($1.value, $2, $3.value);
TREE_NO_WARNING ($$.value) = 1;
$$.original_code = ERROR_MARK;
}
;
primary:
IDENTIFIER
{
if (yychar == YYEMPTY)
yychar = YYLEX;
$$.value = build_external_ref ($1, yychar == '(');
$$.original_code = ERROR_MARK;
}
| CONSTANT
{ $$.value = $1; $$.original_code = ERROR_MARK; }
| STRING
{ $$.value = $1; $$.original_code = STRING_CST; }
| FUNC_NAME
{ $$.value = fname_decl (C_RID_CODE ($1), $1);
$$.original_code = ERROR_MARK; }
| '(' typename ')' '{'
{ start_init (NULL_TREE, NULL, 0);
$<ttype>$ = groktypename ($2);
if (C_TYPE_VARIABLE_SIZE ($<ttype>$))
{
error ("compound literal has variable size");
$<ttype>$ = error_mark_node;
}
really_start_incremental_init ($<ttype>$); }
initlist_maybe_comma '}' %prec UNARY
{ struct c_expr init = pop_init_level (0);
tree constructor = init.value;
tree type = $<ttype>5;
finish_init ();
maybe_warn_string_init (type, init);
/* APPLE LOCAL AltiVec (in 4.2 o) */
if (pedantic && TREE_CODE (type) != VECTOR_TYPE && !flag_isoc99)
pedwarn ("ISO C90 forbids compound literals");
$$.value = build_compound_literal (type, constructor);
$$.original_code = ERROR_MARK;
}
| '(' expr ')'
{ $$.value = $2.value;
if (TREE_CODE ($$.value) == MODIFY_EXPR)
TREE_NO_WARNING ($$.value) = 1;
$$.original_code = ERROR_MARK; }
| '(' error ')'
{ $$.value = error_mark_node; $$.original_code = ERROR_MARK; }
| compstmt_primary_start compstmt_nostart ')'
{ if (pedantic)
pedwarn ("ISO C forbids braced-groups within expressions");
$$.value = c_finish_stmt_expr ($1);
$$.original_code = ERROR_MARK;
}
| compstmt_primary_start error ')'
{ c_finish_stmt_expr ($1);
$$.value = error_mark_node;
$$.original_code = ERROR_MARK;
}
| primary '(' exprlist ')' %prec '.'
{ $$.value = build_function_call ($1.value, $3);
$$.original_code = ERROR_MARK; }
| VA_ARG '(' expr_no_commas ',' typename ')'
{ $$.value = build_va_arg ($3.value, groktypename ($5));
$$.original_code = ERROR_MARK; }
| OFFSETOF '(' typename ','
{ tree type = groktypename ($3);
if (type == error_mark_node)
offsetof_base = error_mark_node;
else
offsetof_base = build1 (INDIRECT_REF, type, NULL);
}
offsetof_member_designator ')'
{ $$.value = fold_offsetof ($6);
$$.original_code = ERROR_MARK; }
| OFFSETOF '(' error ')'
{ $$.value = error_mark_node; $$.original_code = ERROR_MARK; }
| CHOOSE_EXPR '(' expr_no_commas ',' expr_no_commas ','
expr_no_commas ')'
{
tree c;
c = fold ($3.value);
STRIP_NOPS (c);
if (TREE_CODE (c) != INTEGER_CST)
error ("first argument to %<__builtin_choose_expr%> not"
" a constant");
$$ = integer_zerop (c) ? $7 : $5;
}
| CHOOSE_EXPR '(' error ')'
{ $$.value = error_mark_node; $$.original_code = ERROR_MARK; }
| TYPES_COMPATIBLE_P '(' typename ',' typename ')'
{
tree e1, e2;
e1 = TYPE_MAIN_VARIANT (groktypename ($3));
e2 = TYPE_MAIN_VARIANT (groktypename ($5));
$$.value = comptypes (e1, e2)
? build_int_cst (NULL_TREE, 1)
: build_int_cst (NULL_TREE, 0);
$$.original_code = ERROR_MARK;
}
| TYPES_COMPATIBLE_P '(' error ')'
{ $$.value = error_mark_node; $$.original_code = ERROR_MARK; }
| primary '[' expr ']' %prec '.'
{ $$.value = build_array_ref ($1.value, $3.value);
$$.original_code = ERROR_MARK; }
| primary '.' identifier
{ $$.value = build_component_ref ($1.value, $3);
$$.original_code = ERROR_MARK; }
| primary POINTSAT identifier
{
tree expr = build_indirect_ref ($1.value, "->");
$$.value = build_component_ref (expr, $3);
$$.original_code = ERROR_MARK;
}
| primary PLUSPLUS
{ $$.value = build_unary_op (POSTINCREMENT_EXPR, $1.value, 0);
$$.original_code = ERROR_MARK; }
| primary MINUSMINUS
{ $$.value = build_unary_op (POSTDECREMENT_EXPR, $1.value, 0);
$$.original_code = ERROR_MARK; }
@@ifobjc
| objcmessageexpr
{ $$.value = objc_build_message_expr ($1);
$$.original_code = ERROR_MARK; }
| objcselectorexpr
{ $$.value = objc_build_selector_expr ($1);
$$.original_code = ERROR_MARK; }
| objcprotocolexpr
{ $$.value = objc_build_protocol_expr ($1);
$$.original_code = ERROR_MARK; }
| objcencodeexpr
{ $$.value = objc_build_encode_expr ($1);
$$.original_code = ERROR_MARK; }
| OBJC_STRING
{ $$.value = objc_build_string_object ($1);
$$.original_code = ERROR_MARK; }
@@end_ifobjc
;
/* This is the second argument to __builtin_offsetof. We must have one
identifier, and beyond that we want to accept sub structure and sub
array references. */
offsetof_member_designator:
identifier
{ $$ = build_component_ref (offsetof_base, $1); }
| offsetof_member_designator '.' identifier
{ $$ = build_component_ref ($1, $3); }
| offsetof_member_designator '[' expr ']'
{ $$ = build_array_ref ($1, $3.value); }
;
old_style_parm_decls:
/* empty */
| datadecls
;
/* The following are analogous to lineno_decl, decls and decl
except that they do not allow nested functions.
They are used for old-style parm decls. */
lineno_datadecl:
save_location datadecl
{ }
;
datadecls:
lineno_datadecl
| errstmt
| datadecls lineno_datadecl
| lineno_datadecl errstmt
;
/* We don't allow prefix attributes here because they cause reduce/reduce
conflicts: we can't know whether we're parsing a function decl with
attribute suffix, or function defn with attribute prefix on first old
style parm. */
datadecl:
declspecs_ts_nosa setspecs initdecls ';'
{ POP_DECLSPEC_STACK; }
| declspecs_nots_nosa setspecs notype_initdecls ';'
{ POP_DECLSPEC_STACK; }
| declspecs_ts_nosa ';'
{ shadow_tag_warned (finish_declspecs ($1), 1);
pedwarn ("empty declaration"); }
| declspecs_nots_nosa ';'
{ pedwarn ("empty declaration"); }
;
/* This combination which saves a lineno before a decl
is the normal thing to use, rather than decl itself.
This is to avoid shift/reduce conflicts in contexts
where statement labels are allowed. */
lineno_decl:
save_location decl
/* APPLE LOCAL CW asm blocks (in 4.2 al) */
{ if (flag_iasm_blocks) iasm_in_decl = false; }
;
/* records the type and storage class specs to use for processing
the declarators that follow.
Maintains a stack of outer-level values of current_declspecs,
for the sake of parm declarations nested in function declarators. */
setspecs: /* empty */
{ pending_xref_error ();
PUSH_DECLSPEC_STACK;
if ($<dsptype>0)
{
prefix_attributes = $<dsptype>0->attrs;
$<dsptype>0->attrs = NULL_TREE;
current_declspecs = $<dsptype>0;
}
else
{
prefix_attributes = NULL_TREE;
current_declspecs = build_null_declspecs ();
}
current_declspecs = finish_declspecs (current_declspecs);
all_prefix_attributes = prefix_attributes; }
;
/* Possibly attributes after a comma, which should reset all_prefix_attributes
to prefix_attributes with these ones chained on the front. */
maybe_resetattrs:
maybe_attribute
{ all_prefix_attributes = chainon ($1, prefix_attributes); }
;
decl:
declspecs_ts setspecs initdecls ';'
{ POP_DECLSPEC_STACK; }
| declspecs_nots setspecs notype_initdecls ';'
{ POP_DECLSPEC_STACK; }
| declspecs_ts setspecs nested_function
{ POP_DECLSPEC_STACK; }
| declspecs_nots setspecs notype_nested_function
{ POP_DECLSPEC_STACK; }
| declspecs ';'
{ shadow_tag (finish_declspecs ($1)); }
| extension decl
{ RESTORE_EXT_FLAGS ($1); }
;
/* A list of declaration specifiers. These are:
- Storage class specifiers (scspec), which for GCC currently includes
function specifiers ("inline").
- Type specifiers (typespec_*).
- Type qualifiers (TYPE_QUAL).
- Attribute specifier lists (attributes).
The various cases below are classified according to:
(a) Whether a storage class specifier is included or not; some
places in the grammar disallow storage class specifiers (_sc or _nosc).
(b) Whether a type specifier has been seen; after a type specifier,
a typedef name is an identifier to redeclare (_ts or _nots).
(c) Whether the list starts with an attribute; in certain places,
the grammar requires specifiers that don't start with an attribute
(_sa or _nosa).
(d) Whether the list ends with an attribute (or a specifier such that
any following attribute would have been parsed as part of that specifier);
this avoids shift-reduce conflicts in the parsing of attributes
(_ea or _noea).
TODO:
(i) Distinguish between function specifiers and storage class specifiers,
at least for the purpose of warnings about obsolescent usage.
(ii) Halve the number of productions here by eliminating the _sc/_nosc
distinction and instead checking where required that storage class
specifiers aren't present. */
/* Declspecs which contain at least one type specifier or typedef name.
(Just `const' or `volatile' is not enough.)
A typedef'd name following these is taken as a name to be declared. */
declspecs_nosc_nots_nosa_noea:
TYPE_QUAL
{ $$ = declspecs_add_qual (build_null_declspecs (), $1); }
| declspecs_nosc_nots_nosa_noea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_nosc_nots_nosa_ea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
;
declspecs_nosc_nots_nosa_ea:
declspecs_nosc_nots_nosa_noea attributes
{ $$ = declspecs_add_attrs ($1, $2); }
;
declspecs_nosc_nots_sa_noea:
declspecs_nosc_nots_sa_noea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_nosc_nots_sa_ea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
;
declspecs_nosc_nots_sa_ea:
attributes
{ $$ = declspecs_add_attrs (build_null_declspecs (), $1); }
| declspecs_nosc_nots_sa_noea attributes
{ $$ = declspecs_add_attrs ($1, $2); }
;
declspecs_nosc_ts_nosa_noea:
typespec_nonattr
{ $$ = declspecs_add_type (build_null_declspecs (), $1); }
| declspecs_nosc_ts_nosa_noea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_nosc_ts_nosa_ea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_nosc_ts_nosa_noea typespec_reserved_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_ts_nosa_ea typespec_reserved_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_nots_nosa_noea typespec_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_nots_nosa_ea typespec_nonattr
{ $$ = declspecs_add_type ($1, $2); }
;
declspecs_nosc_ts_nosa_ea:
typespec_attr
{ $$ = declspecs_add_type (build_null_declspecs (), $1); }
| declspecs_nosc_ts_nosa_noea attributes
{ $$ = declspecs_add_attrs ($1, $2); }
| declspecs_nosc_ts_nosa_noea typespec_reserved_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_ts_nosa_ea typespec_reserved_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_nots_nosa_noea typespec_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_nots_nosa_ea typespec_attr
{ $$ = declspecs_add_type ($1, $2); }
;
declspecs_nosc_ts_sa_noea:
declspecs_nosc_ts_sa_noea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_nosc_ts_sa_ea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_nosc_ts_sa_noea typespec_reserved_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_ts_sa_ea typespec_reserved_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_nots_sa_noea typespec_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_nots_sa_ea typespec_nonattr
{ $$ = declspecs_add_type ($1, $2); }
;
declspecs_nosc_ts_sa_ea:
declspecs_nosc_ts_sa_noea attributes
{ $$ = declspecs_add_attrs ($1, $2); }
| declspecs_nosc_ts_sa_noea typespec_reserved_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_ts_sa_ea typespec_reserved_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_nots_sa_noea typespec_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_nots_sa_ea typespec_attr
{ $$ = declspecs_add_type ($1, $2); }
;
declspecs_sc_nots_nosa_noea:
scspec
{ $$ = declspecs_add_scspec (build_null_declspecs (), $1); }
| declspecs_sc_nots_nosa_noea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_sc_nots_nosa_ea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_nosc_nots_nosa_noea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_nosc_nots_nosa_ea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_sc_nots_nosa_noea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_sc_nots_nosa_ea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
;
declspecs_sc_nots_nosa_ea:
declspecs_sc_nots_nosa_noea attributes
{ $$ = declspecs_add_attrs ($1, $2); }
;
declspecs_sc_nots_sa_noea:
declspecs_sc_nots_sa_noea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_sc_nots_sa_ea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_nosc_nots_sa_noea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_nosc_nots_sa_ea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_sc_nots_sa_noea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_sc_nots_sa_ea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
;
declspecs_sc_nots_sa_ea:
declspecs_sc_nots_sa_noea attributes
{ $$ = declspecs_add_attrs ($1, $2); }
;
declspecs_sc_ts_nosa_noea:
declspecs_sc_ts_nosa_noea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_sc_ts_nosa_ea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_sc_ts_nosa_noea typespec_reserved_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_ts_nosa_ea typespec_reserved_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_nots_nosa_noea typespec_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_nots_nosa_ea typespec_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_ts_nosa_noea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_nosc_ts_nosa_ea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_sc_ts_nosa_noea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_sc_ts_nosa_ea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
;
declspecs_sc_ts_nosa_ea:
declspecs_sc_ts_nosa_noea attributes
{ $$ = declspecs_add_attrs ($1, $2); }
| declspecs_sc_ts_nosa_noea typespec_reserved_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_ts_nosa_ea typespec_reserved_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_nots_nosa_noea typespec_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_nots_nosa_ea typespec_attr
{ $$ = declspecs_add_type ($1, $2); }
;
declspecs_sc_ts_sa_noea:
declspecs_sc_ts_sa_noea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_sc_ts_sa_ea TYPE_QUAL
{ $$ = declspecs_add_qual ($1, $2); }
| declspecs_sc_ts_sa_noea typespec_reserved_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_ts_sa_ea typespec_reserved_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_nots_sa_noea typespec_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_nots_sa_ea typespec_nonattr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_nosc_ts_sa_noea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_nosc_ts_sa_ea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_sc_ts_sa_noea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
| declspecs_sc_ts_sa_ea scspec
{ $$ = declspecs_add_scspec ($1, $2); }
;
declspecs_sc_ts_sa_ea:
declspecs_sc_ts_sa_noea attributes
{ $$ = declspecs_add_attrs ($1, $2); }
| declspecs_sc_ts_sa_noea typespec_reserved_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_ts_sa_ea typespec_reserved_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_nots_sa_noea typespec_attr
{ $$ = declspecs_add_type ($1, $2); }
| declspecs_sc_nots_sa_ea typespec_attr
{ $$ = declspecs_add_type ($1, $2); }
;
/* Particular useful classes of declspecs. */
declspecs_ts:
declspecs_nosc_ts_nosa_noea
| declspecs_nosc_ts_nosa_ea
| declspecs_nosc_ts_sa_noea
| declspecs_nosc_ts_sa_ea
| declspecs_sc_ts_nosa_noea
| declspecs_sc_ts_nosa_ea
| declspecs_sc_ts_sa_noea
| declspecs_sc_ts_sa_ea
;
declspecs_nots:
declspecs_nosc_nots_nosa_noea
| declspecs_nosc_nots_nosa_ea
| declspecs_nosc_nots_sa_noea
| declspecs_nosc_nots_sa_ea
| declspecs_sc_nots_nosa_noea
| declspecs_sc_nots_nosa_ea
| declspecs_sc_nots_sa_noea
| declspecs_sc_nots_sa_ea
;
declspecs_ts_nosa:
declspecs_nosc_ts_nosa_noea
| declspecs_nosc_ts_nosa_ea
| declspecs_sc_ts_nosa_noea
| declspecs_sc_ts_nosa_ea
;
declspecs_nots_nosa:
declspecs_nosc_nots_nosa_noea
| declspecs_nosc_nots_nosa_ea
| declspecs_sc_nots_nosa_noea
| declspecs_sc_nots_nosa_ea
;
declspecs_nosc_ts:
declspecs_nosc_ts_nosa_noea
| declspecs_nosc_ts_nosa_ea
| declspecs_nosc_ts_sa_noea
| declspecs_nosc_ts_sa_ea
;
declspecs_nosc_nots:
declspecs_nosc_nots_nosa_noea
| declspecs_nosc_nots_nosa_ea
| declspecs_nosc_nots_sa_noea
| declspecs_nosc_nots_sa_ea
;
declspecs_nosc:
declspecs_nosc_ts_nosa_noea
| declspecs_nosc_ts_nosa_ea
| declspecs_nosc_ts_sa_noea
| declspecs_nosc_ts_sa_ea
| declspecs_nosc_nots_nosa_noea
| declspecs_nosc_nots_nosa_ea
| declspecs_nosc_nots_sa_noea
| declspecs_nosc_nots_sa_ea
;
declspecs:
declspecs_nosc_nots_nosa_noea
| declspecs_nosc_nots_nosa_ea
| declspecs_nosc_nots_sa_noea
| declspecs_nosc_nots_sa_ea
| declspecs_nosc_ts_nosa_noea
| declspecs_nosc_ts_nosa_ea
| declspecs_nosc_ts_sa_noea
| declspecs_nosc_ts_sa_ea
| declspecs_sc_nots_nosa_noea
| declspecs_sc_nots_nosa_ea
| declspecs_sc_nots_sa_noea
| declspecs_sc_nots_sa_ea
| declspecs_sc_ts_nosa_noea
| declspecs_sc_ts_nosa_ea
| declspecs_sc_ts_sa_noea
| declspecs_sc_ts_sa_ea
;
/* A (possibly empty) sequence of type qualifiers and attributes. */
maybe_type_quals_attrs:
/* empty */
{ $$ = NULL; }
| declspecs_nosc_nots
{ $$ = $1; }
;
/* A type specifier (but not a type qualifier).
Once we have seen one of these in a declaration,
if a typedef name appears then it is being redeclared.
The _reserved versions start with a reserved word and may appear anywhere
in the declaration specifiers; the _nonreserved versions may only
appear before any other type specifiers, and after that are (if names)
being redeclared.
FIXME: should the _nonreserved version be restricted to names being
redeclared only? The other entries there relate only the GNU extensions
and Objective C, and are historically parsed thus, and don't make sense
after other type specifiers, but it might be cleaner to count them as
_reserved.
_attr means: specifiers that either end with attributes,
or are such that any following attributes would
be parsed as part of the specifier.
_nonattr: other specifiers not ending with attributes. */
typespec_nonattr:
typespec_reserved_nonattr
| typespec_nonreserved_nonattr
;
typespec_attr:
typespec_reserved_attr
;
typespec_reserved_nonattr:
TYPESPEC
{ OBJC_NEED_RAW_IDENTIFIER (1);
$$.kind = ctsk_resword;
$$.spec = $1; }
| structsp_nonattr
;
typespec_reserved_attr:
structsp_attr
;
typespec_nonreserved_nonattr:
TYPENAME
{ /* For a typedef name, record the meaning, not the name.
In case of `foo foo, bar;'. */
$$.kind = ctsk_typedef;
$$.spec = lookup_name ($1); }
@@ifobjc
| CLASSNAME protocolrefs
{ $$.kind = ctsk_objc;
$$.spec = objc_get_protocol_qualified_type ($1, $2); }
| TYPENAME non_empty_protocolrefs
{ $$.kind = ctsk_objc;
$$.spec = objc_get_protocol_qualified_type ($1, $2); }
/* Make "<SomeProtocol>" equivalent to "id <SomeProtocol>"
- nisse@lysator.liu.se */
| non_empty_protocolrefs
{ $$.kind = ctsk_objc;
$$.spec = objc_get_protocol_qualified_type (NULL_TREE, $1); }
@@end_ifobjc
| typeof '(' expr ')'
/* APPLE LOCAL begin mainline 2006-05-18 4336222 */
{ bool was_vm;
skip_evaluation--;
in_typeof--;
if (TREE_CODE ($3.value) == COMPONENT_REF
&& DECL_C_BIT_FIELD (TREE_OPERAND ($3.value, 1)))
error ("%<typeof%> applied to a bit-field");
$$.kind = ctsk_typeof;
$$.spec = TREE_TYPE ($3.value);
/* APPLE LOCAL begin radar 4204796 (in 4.2 n) */
if (c_dialect_objc()
&& lookup_attribute ("objc_volatilized", TYPE_ATTRIBUTES ($$.spec)))
$$.spec = build_qualified_type
($$.spec, (TYPE_QUALS ($$.spec) & ~TYPE_QUAL_VOLATILE));
/* APPLE LOCAL end radar 4204796 (in 4.2 n) */
was_vm = variably_modified_type_p ($$.spec, NULL_TREE);
/* This should be returned with the type so that when the type
is evaluated, this can be evaluated. For now, we avoid
evaluation when the context might. */
if (!skip_evaluation && was_vm)
c_finish_expr_stmt ($3.value);
pop_maybe_used (was_vm); }
/* APPLE LOCAL end mainline 2006-05-18 4336222 */
| typeof '(' typename ')'
{ skip_evaluation--;
in_typeof--;
$$.kind = ctsk_typeof;
$$.spec = groktypename ($3);
pop_maybe_used (variably_modified_type_p ($$.spec,
NULL_TREE)); }
;
/* typespec_nonreserved_attr does not exist. */
initdecls:
initdcl
| initdecls ',' maybe_resetattrs initdcl
;
notype_initdecls:
notype_initdcl
| notype_initdecls ',' maybe_resetattrs notype_initdcl
;
initdcl:
declarator maybeasm maybe_attribute '='
{ $<ttype>$ = start_decl ($1, current_declspecs, true,
chainon ($3, all_prefix_attributes));
if (!$<ttype>$)
$<ttype>$ = error_mark_node;
start_init ($<ttype>$, $2, global_bindings_p ()); }
init
/* Note how the declaration of the variable is in effect while its init is parsed! */
{ finish_init ();
if ($<ttype>5 != error_mark_node)
{
maybe_warn_string_init (TREE_TYPE ($<ttype>5), $6);
finish_decl ($<ttype>5, $6.value, $2);
}
}
| declarator maybeasm maybe_attribute
{ tree d = start_decl ($1, current_declspecs, false,
chainon ($3, all_prefix_attributes));
if (d)
finish_decl (d, NULL_TREE, $2);
}
;
notype_initdcl:
notype_declarator maybeasm maybe_attribute '='
{ $<ttype>$ = start_decl ($1, current_declspecs, true,
chainon ($3, all_prefix_attributes));
if (!$<ttype>$)
$<ttype>$ = error_mark_node;
start_init ($<ttype>$, $2, global_bindings_p ()); }
init
/* Note how the declaration of the variable is in effect while its init is parsed! */
{ finish_init ();
if ($<ttype>5 != error_mark_node)
{
maybe_warn_string_init (TREE_TYPE ($<ttype>5), $6);
finish_decl ($<ttype>5, $6.value, $2);
}
}
| notype_declarator maybeasm maybe_attribute
{ tree d = start_decl ($1, current_declspecs, false,
chainon ($3, all_prefix_attributes));
if (d)
finish_decl (d, NULL_TREE, $2); }
;
/* the * rules are dummies to accept the Apollo extended syntax
so that the header files compile. */
maybe_attribute:
/* empty */
{ $$ = NULL_TREE; }
| attributes
{ $$ = $1; }
;
attributes:
attribute
{ $$ = $1; }
| attributes attribute
{ $$ = chainon ($1, $2); }
;
attribute:
ATTRIBUTE stop_string_translation
'(' '(' attribute_list ')' ')' start_string_translation
{ $$ = $5; }
| ATTRIBUTE error start_string_translation
{ $$ = NULL_TREE; }
;
attribute_list:
attrib
{ $$ = $1; }
| attribute_list ',' attrib
{ $$ = chainon ($1, $3); }
;
attrib:
/* empty */
{ $$ = NULL_TREE; }
| any_word
{ $$ = build_tree_list ($1, NULL_TREE); }
| any_word '(' IDENTIFIER ')'
{ $$ = build_tree_list ($1, build_tree_list (NULL_TREE, $3)); }
| any_word '(' IDENTIFIER ',' nonnull_exprlist ')'
{ $$ = build_tree_list ($1, tree_cons (NULL_TREE, $3, $5)); }
| any_word '(' exprlist ')'
{ $$ = build_tree_list ($1, $3); }
;
/* This still leaves out most reserved keywords,
shouldn't we include them? */
any_word:
identifier
| scspec
| TYPESPEC
| TYPE_QUAL
;
scspec:
STATIC
/* APPLE LOCAL CW asm blocks (in 4.2 ac) */
| IASM_ASM_KEYWORD
| SCSPEC
;
/* Initializers. `init' is the entry point. */
init:
expr_no_commas
{ $$ = $1; }
| '{'
{ really_start_incremental_init (NULL_TREE); }
initlist_maybe_comma '}'
{ $$ = pop_init_level (0); }
| error
{ $$.value = error_mark_node; $$.original_code = ERROR_MARK; }
;
/* `initlist_maybe_comma' is the guts of an initializer in braces. */
initlist_maybe_comma:
/* empty */
{ if (pedantic)
pedwarn ("ISO C forbids empty initializer braces"); }
| initlist1 maybecomma
;
initlist1:
initelt
| initlist1 ',' initelt
;
/* `initelt' is a single element of an initializer.
It may use braces. */
initelt:
designator_list '=' initval
{ if (pedantic && !flag_isoc99)
pedwarn ("ISO C90 forbids specifying subobject to initialize"); }
| array_designator initval
{ if (pedantic)
pedwarn ("obsolete use of designated initializer without %<=%>"); }
| identifier ':'
{ set_init_label ($1);
if (pedantic)
pedwarn ("obsolete use of designated initializer with %<:%>"); }
initval
{}
| initval
;
initval:
'{'
{ push_init_level (0); }
initlist_maybe_comma '}'
{ process_init_element (pop_init_level (0)); }
| expr_no_commas
{ process_init_element ($1); }
| error
;
designator_list:
designator
| designator_list designator
;
designator:
'.' identifier
{ set_init_label ($2); }
| array_designator
;
array_designator:
'[' expr_no_commas ELLIPSIS expr_no_commas ']'
{ set_init_index ($2.value, $4.value);
if (pedantic)
pedwarn ("ISO C forbids specifying range of elements to initialize"); }
| '[' expr_no_commas ']'
{ set_init_index ($2.value, NULL_TREE); }
;
nested_function:
declarator
{ if (pedantic)
pedwarn ("ISO C forbids nested functions");
/* APPLE LOCAL begin nested functions 4258406 4357979 (in 4.2 m) */
else if (flag_nested_functions == 0)
error ("nested functions are disabled, use -fnested-functions to re-enable");
/* APPLE LOCAL end nested functions 4258406 4357979 (in 4.2 m) */
push_function_context ();
if (!start_function (current_declspecs, $1,
all_prefix_attributes))
{
pop_function_context ();
YYERROR1;
}
}
old_style_parm_decls save_location
{ tree decl = current_function_decl;
DECL_SOURCE_LOCATION (decl) = $4;
store_parm_decls (); }
/* This used to use compstmt_or_error. That caused a bug with
input `f(g) int g {}', where the use of YYERROR1 above caused
an error which then was handled by compstmt_or_error. There
followed a repeated execution of that same rule, which called
YYERROR1 again, and so on. */
compstmt
{ tree decl = current_function_decl;
add_stmt ($6);
finish_function ();
pop_function_context ();
add_stmt (build_stmt (DECL_EXPR, decl)); }
;
notype_nested_function:
notype_declarator
{ if (pedantic)
pedwarn ("ISO C forbids nested functions");
/* APPLE LOCAL begin nested functions 4258406 4357979 (in 4.2 m) */
else if (flag_nested_functions == 0)
error ("nested functions are disabled, use -fnested-functions to re-enable");
/* APPLE LOCAL end nested functions 4258406 4357979 (in 4.2 m) */
push_function_context ();
if (!start_function (current_declspecs, $1,
all_prefix_attributes))
{
pop_function_context ();
YYERROR1;
}
}
old_style_parm_decls save_location
{ tree decl = current_function_decl;
DECL_SOURCE_LOCATION (decl) = $4;
store_parm_decls (); }
/* This used to use compstmt_or_error. That caused a bug with
input `f(g) int g {}', where the use of YYERROR1 above caused
an error which then was handled by compstmt_or_error. There
followed a repeated execution of that same rule, which called
YYERROR1 again, and so on. */
compstmt
{ tree decl = current_function_decl;
add_stmt ($6);
finish_function ();
pop_function_context ();
add_stmt (build_stmt (DECL_EXPR, decl)); }
;
/* Any kind of declarator (thus, all declarators allowed
after an explicit typespec). */
declarator:
after_type_declarator
| notype_declarator
;
/* A declarator that is allowed only after an explicit typespec. */
after_type_declarator:
'(' maybe_attribute after_type_declarator ')'
{ $$ = $2 ? build_attrs_declarator ($2, $3) : $3; }
| after_type_declarator '(' parmlist_or_identifiers %prec '.'
{ $$ = build_function_declarator ($3, $1); }
| after_type_declarator array_declarator %prec '.'
{ $$ = set_array_declarator_inner ($2, $1, false); }
| '*' maybe_type_quals_attrs after_type_declarator %prec UNARY
{ $$ = make_pointer_declarator ($2, $3); }
| TYPENAME
{ $$ = build_id_declarator ($1); }
/* APPLE LOCAL begin radar 4281748 */
@@ifobjc
| CLASSNAME
{ $$ = build_id_declarator ($1); }
@@end_ifobjc
/* APPLE LOCAL end radar 4281748 */
;
/* Kinds of declarator that can appear in a parameter list
in addition to notype_declarator. This is like after_type_declarator
but does not allow a typedef name in parentheses as an identifier
(because it would conflict with a function with that typedef as arg). */
parm_declarator:
parm_declarator_starttypename
| parm_declarator_nostarttypename
;
parm_declarator_starttypename:
parm_declarator_starttypename '(' parmlist_or_identifiers %prec '.'
{ $$ = build_function_declarator ($3, $1); }
| parm_declarator_starttypename array_declarator %prec '.'
{ $$ = set_array_declarator_inner ($2, $1, false); }
| TYPENAME
{ $$ = build_id_declarator ($1); }
;
parm_declarator_nostarttypename:
parm_declarator_nostarttypename '(' parmlist_or_identifiers %prec '.'
{ $$ = build_function_declarator ($3, $1); }
| parm_declarator_nostarttypename array_declarator %prec '.'
{ $$ = set_array_declarator_inner ($2, $1, false); }
| '*' maybe_type_quals_attrs parm_declarator_starttypename %prec UNARY
{ $$ = make_pointer_declarator ($2, $3); }
| '*' maybe_type_quals_attrs parm_declarator_nostarttypename %prec UNARY
{ $$ = make_pointer_declarator ($2, $3); }
| '(' maybe_attribute parm_declarator_nostarttypename ')'
{ $$ = $2 ? build_attrs_declarator ($2, $3) : $3; }
;
/* A declarator allowed whether or not there has been
an explicit typespec. These cannot redeclare a typedef-name. */
notype_declarator:
notype_declarator '(' parmlist_or_identifiers %prec '.'
{ $$ = build_function_declarator ($3, $1); }
| '(' maybe_attribute notype_declarator ')'
{ $$ = $2 ? build_attrs_declarator ($2, $3) : $3; }
| '*' maybe_type_quals_attrs notype_declarator %prec UNARY
{ $$ = make_pointer_declarator ($2, $3); }
| notype_declarator array_declarator %prec '.'
{ $$ = set_array_declarator_inner ($2, $1, false); }
| IDENTIFIER
{ $$ = build_id_declarator ($1); }
;
struct_head:
STRUCT
{ $$ = NULL_TREE; }
| STRUCT attributes
{ $$ = $2; }
;
union_head:
UNION
{ $$ = NULL_TREE; }
| UNION attributes
{ $$ = $2; }
;
enum_head:
ENUM
{ $$ = NULL_TREE; }
| ENUM attributes
{ $$ = $2; }
;
/* structsp_attr: struct/union/enum specifiers that either
end with attributes, or are such that any following attributes would
be parsed as part of the struct/union/enum specifier.
structsp_nonattr: other struct/union/enum specifiers. */
structsp_attr:
struct_head identifier '{'
{ $<ttype>$ = start_struct (RECORD_TYPE, $2);
/* Start scope of tag before parsing components. */
}
component_decl_list '}' maybe_attribute
{ $$.spec = finish_struct ($<ttype>4, nreverse ($5),
chainon ($1, $7));
$$.kind = ctsk_tagdef; }
| struct_head '{' component_decl_list '}' maybe_attribute
{ $$.spec = finish_struct (start_struct (RECORD_TYPE,
NULL_TREE),
nreverse ($3), chainon ($1, $5));
$$.kind = ctsk_tagdef;
}
| union_head identifier '{'
{ $<ttype>$ = start_struct (UNION_TYPE, $2); }
component_decl_list '}' maybe_attribute
{ $$.spec = finish_struct ($<ttype>4, nreverse ($5),
chainon ($1, $7));
$$.kind = ctsk_tagdef; }
| union_head '{' component_decl_list '}' maybe_attribute
{ $$.spec = finish_struct (start_struct (UNION_TYPE,
NULL_TREE),
nreverse ($3), chainon ($1, $5));
$$.kind = ctsk_tagdef;
}
| enum_head identifier '{'
{ $<ttype>$ = start_enum ($2); }
enumlist maybecomma_warn '}' maybe_attribute
{ $$.spec = finish_enum ($<ttype>4, nreverse ($5),
chainon ($1, $8));
$$.kind = ctsk_tagdef; }
| enum_head '{'
{ $<ttype>$ = start_enum (NULL_TREE); }
enumlist maybecomma_warn '}' maybe_attribute
{ $$.spec = finish_enum ($<ttype>3, nreverse ($4),
chainon ($1, $7));
$$.kind = ctsk_tagdef; }
;
structsp_nonattr:
struct_head identifier
{ $$ = parser_xref_tag (RECORD_TYPE, $2); }
| union_head identifier
{ $$ = parser_xref_tag (UNION_TYPE, $2); }
| enum_head identifier
{ $$ = parser_xref_tag (ENUMERAL_TYPE, $2);
/* In ISO C, enumerated types can be referred to
only if already defined. */
if (pedantic && !COMPLETE_TYPE_P ($$.spec))
pedwarn ("ISO C forbids forward references to %<enum%> types"); }
;
maybecomma:
/* empty */
| ','
;
maybecomma_warn:
/* empty */
| ','
{ if (pedantic && !flag_isoc99)
pedwarn ("comma at end of enumerator list"); }
;
/* We chain the components in reverse order. They are put in forward
order in structsp_attr.
Note that component_declarator returns single decls, so components
and components_notype can use TREE_CHAIN directly, wheras components
and components_notype return lists (of comma separated decls), so
component_decl_list and component_decl_list2 must use chainon.
The theory behind all this is that there will be more semicolon
separated fields than comma separated fields, and so we'll be
minimizing the number of node traversals required by chainon. */
component_decl_list:
component_decl_list2
{ $$ = $1; }
| component_decl_list2 component_decl
{ $$ = chainon ($2, $1);
pedwarn ("no semicolon at end of struct or union"); }
;
component_decl_list2: /* empty */
{ $$ = NULL_TREE; }
| component_decl_list2 component_decl ';'
{ $$ = chainon ($2, $1); }
| component_decl_list2 ';'
{ if (pedantic)
pedwarn ("extra semicolon in struct or union specified"); }
@@ifobjc
/* foo(sizeof(struct{ @defs(ClassName)})); */
| AT_DEFS '(' CLASSNAME ')'
/* APPLE LOCAL begin C* warnings to easy porting to new abi */
{ $$ = nreverse (objc_get_class_ivars ($3));
if (flag_objc2_check && flag_objc_abi == 1)
warning ("@defs will not be supported in future");
/* APPLE LOCAL radar 4705250 */
else if (flag_objc_abi == 2 && flag_objc_atdefs != 1)
error ("@defs is not supported in new abi");
}
/* APPLE LOCAL end C* warnings to easy porting to new abi */
@@end_ifobjc
;
component_decl:
declspecs_nosc_ts setspecs components
{ $$ = $3;
POP_DECLSPEC_STACK; }
| declspecs_nosc_ts setspecs
{
/* Support for unnamed structs or unions as members of
structs or unions (which is [a] useful and [b] supports
MS P-SDK). */
$$ = grokfield (build_id_declarator (NULL_TREE),
current_declspecs, NULL_TREE);
POP_DECLSPEC_STACK; }
| declspecs_nosc_nots setspecs components_notype
{ $$ = $3;
POP_DECLSPEC_STACK; }
| declspecs_nosc_nots
{ if (pedantic)
pedwarn ("ISO C forbids member declarations with no members");
shadow_tag_warned (finish_declspecs ($1), pedantic);
$$ = NULL_TREE; }
| error
{ $$ = NULL_TREE; }
| extension component_decl
{ $$ = $2;
RESTORE_EXT_FLAGS ($1); }
;
components:
component_declarator
| components ',' maybe_resetattrs component_declarator
{ TREE_CHAIN ($4) = $1; $$ = $4; }
;
components_notype:
component_notype_declarator
| components_notype ',' maybe_resetattrs component_notype_declarator
{ TREE_CHAIN ($4) = $1; $$ = $4; }
;
component_declarator:
declarator maybe_attribute
{ $$ = grokfield ($1, current_declspecs, NULL_TREE);
decl_attributes (&$$,
chainon ($2, all_prefix_attributes), 0); }
| declarator ':' expr_no_commas maybe_attribute
{ $$ = grokfield ($1, current_declspecs, $3.value);
decl_attributes (&$$,
chainon ($4, all_prefix_attributes), 0); }
| ':' expr_no_commas maybe_attribute
{ $$ = grokfield (build_id_declarator (NULL_TREE),
current_declspecs, $2.value);
decl_attributes (&$$,
chainon ($3, all_prefix_attributes), 0); }
;
component_notype_declarator:
notype_declarator maybe_attribute
{ $$ = grokfield ($1, current_declspecs, NULL_TREE);
decl_attributes (&$$,
chainon ($2, all_prefix_attributes), 0); }
| notype_declarator ':' expr_no_commas maybe_attribute
{ $$ = grokfield ($1, current_declspecs, $3.value);
decl_attributes (&$$,
chainon ($4, all_prefix_attributes), 0); }
| ':' expr_no_commas maybe_attribute
{ $$ = grokfield (build_id_declarator (NULL_TREE),
current_declspecs, $2.value);
decl_attributes (&$$,
chainon ($3, all_prefix_attributes), 0); }
;
/* We chain the enumerators in reverse order.
They are put in forward order in structsp_attr. */
enumlist:
enumerator
| enumlist ',' enumerator
{ if ($1 == error_mark_node)
$$ = $1;
else
TREE_CHAIN ($3) = $1, $$ = $3; }
| error
{ $$ = error_mark_node; }
;
enumerator:
identifier
{ $$ = build_enumerator ($1, NULL_TREE); }
| identifier '=' expr_no_commas
{ $$ = build_enumerator ($1, $3.value); }
;
typename:
declspecs_nosc
{ pending_xref_error ();
$<dsptype>$ = finish_declspecs ($1); }
absdcl
{ $$ = XOBNEW (&parser_obstack, struct c_type_name);
$$->specs = $<dsptype>2;
$$->declarator = $3; }
;
absdcl: /* an absolute declarator */
/* empty */
{ $$ = build_id_declarator (NULL_TREE); }
| absdcl1
;
absdcl_maybe_attribute: /* absdcl maybe_attribute, but not just attributes */
/* empty */
{ $$ = build_c_parm (current_declspecs, all_prefix_attributes,
build_id_declarator (NULL_TREE)); }
| absdcl1
{ $$ = build_c_parm (current_declspecs, all_prefix_attributes,
$1); }
| absdcl1_noea attributes
{ $$ = build_c_parm (current_declspecs,
chainon ($2, all_prefix_attributes),
$1); }
;
absdcl1: /* a nonempty absolute declarator */
absdcl1_ea
| absdcl1_noea
;
absdcl1_noea:
direct_absdcl1
| '*' maybe_type_quals_attrs absdcl1_noea
{ $$ = make_pointer_declarator ($2, $3); }
;
absdcl1_ea:
'*' maybe_type_quals_attrs
{ $$ = make_pointer_declarator
($2, build_id_declarator (NULL_TREE)); }
| '*' maybe_type_quals_attrs absdcl1_ea
{ $$ = make_pointer_declarator ($2, $3); }
;
direct_absdcl1:
'(' maybe_attribute absdcl1 ')'
{ $$ = $2 ? build_attrs_declarator ($2, $3) : $3; }
| direct_absdcl1 '(' parmlist
{ $$ = build_function_declarator ($3, $1); }
| direct_absdcl1 array_declarator
{ $$ = set_array_declarator_inner ($2, $1, true); }
| '(' parmlist
{ $$ = build_function_declarator
($2, build_id_declarator (NULL_TREE)); }
| array_declarator
{ $$ = set_array_declarator_inner
($1, build_id_declarator (NULL_TREE), true); }
;
/* The [...] part of a declarator for an array type. */
array_declarator:
'[' maybe_type_quals_attrs expr_no_commas ']'
{ $$ = build_array_declarator ($3.value, $2, false, false); }
| '[' maybe_type_quals_attrs ']'
{ $$ = build_array_declarator (NULL_TREE, $2, false, false); }
| '[' maybe_type_quals_attrs '*' ']'
{ $$ = build_array_declarator (NULL_TREE, $2, false, true); }
| '[' STATIC maybe_type_quals_attrs expr_no_commas ']'
{ $$ = build_array_declarator ($4.value, $3, true, false); }
/* declspecs_nosc_nots is a synonym for type_quals_attrs. */
| '[' declspecs_nosc_nots STATIC expr_no_commas ']'
{ $$ = build_array_declarator ($4.value, $2, true, false); }
;
/* A nonempty series of declarations and statements (possibly followed by
some labels) that can form the body of a compound statement.
NOTE: we don't allow labels on declarations; this might seem like a
natural extension, but there would be a conflict between attributes
on the label and prefix attributes on the declaration. */
stmts_and_decls:
lineno_stmt_decl_or_labels_ending_stmt
| lineno_stmt_decl_or_labels_ending_decl
| lineno_stmt_decl_or_labels_ending_label
{
error ("label at end of compound statement");
}
| lineno_stmt_decl_or_labels_ending_error
;
lineno_stmt_decl_or_labels_ending_stmt:
lineno_stmt
| lineno_stmt_decl_or_labels_ending_stmt lineno_stmt
| lineno_stmt_decl_or_labels_ending_decl lineno_stmt
| lineno_stmt_decl_or_labels_ending_label lineno_stmt
| lineno_stmt_decl_or_labels_ending_error lineno_stmt
;
lineno_stmt_decl_or_labels_ending_decl:
lineno_decl
| lineno_stmt_decl_or_labels_ending_stmt lineno_decl
{
if ((pedantic && !flag_isoc99)
|| warn_declaration_after_statement)
pedwarn_c90 ("ISO C90 forbids mixed declarations and code");
}
| lineno_stmt_decl_or_labels_ending_decl lineno_decl
| lineno_stmt_decl_or_labels_ending_error lineno_decl
;
lineno_stmt_decl_or_labels_ending_label:
lineno_label
| lineno_stmt_decl_or_labels_ending_stmt lineno_label
| lineno_stmt_decl_or_labels_ending_decl lineno_label
| lineno_stmt_decl_or_labels_ending_label lineno_label
| lineno_stmt_decl_or_labels_ending_error lineno_label
;
lineno_stmt_decl_or_labels_ending_error:
errstmt
| lineno_stmt_decl_or_labels errstmt
;
lineno_stmt_decl_or_labels:
lineno_stmt_decl_or_labels_ending_stmt
| lineno_stmt_decl_or_labels_ending_decl
| lineno_stmt_decl_or_labels_ending_label
| lineno_stmt_decl_or_labels_ending_error
;
errstmt: error ';'
;
/* Start and end blocks created for the new scopes of C99. */
c99_block_start: /* empty */
/* APPLE LOCAL begin radar 4472881 (in 4.2 ah) */
{ $$ = c_begin_compound_stmt (
flag_isoc99
|| (c_dialect_objc() && objc_foreach_context)); }
/* APPLE LOCAL end radar 4472881 (in 4.2 ah) */
;
/* Read zero or more forward-declarations for labels
that nested functions can jump to. */
maybe_label_decls:
/* empty */
| label_decls
{ if (pedantic)
pedwarn ("ISO C forbids label declarations"); }
;
label_decls:
label_decl
| label_decls label_decl
;
label_decl:
LABEL identifiers_or_typenames ';'
{ tree link;
for (link = $2; link; link = TREE_CHAIN (link))
{
tree label = declare_label (TREE_VALUE (link));
C_DECLARED_LABEL_FLAG (label) = 1;
add_stmt (build_stmt (DECL_EXPR, label));
}
}
;
/* This is the body of a function definition.
It causes syntax errors to ignore to the next openbrace. */
compstmt_or_error:
compstmt
{ add_stmt ($1); }
| error compstmt
;
compstmt_start: '{' { $$ = c_begin_compound_stmt (true); }
;
compstmt_nostart: '}'
| maybe_label_decls compstmt_contents_nonempty '}'
/* APPLE LOCAL begin CW asm blocks (in 4.2 am) */
{
if (flag_iasm_blocks)
iasm_end_block ();
}
/* APPLE LOCAL end CW asm blocks */
;
compstmt_contents_nonempty:
stmts_and_decls
| error
;
compstmt_primary_start:
'(' '{'
{ if (cur_stmt_list == NULL)
{
error ("braced-group within expression allowed "
"only inside a function");
YYERROR;
}
$$ = c_begin_stmt_expr ();
}
;
compstmt: compstmt_start compstmt_nostart
{ $$ = c_end_compound_stmt ($1, true); }
;
/* APPLE LOCAL begin CW asm blocks */
/* (in 4.2 ax) */
iasm_save_location: save_location
{ iasm_lineno = input_line; }
;
/* (in 4.2 au) */
/* A CW-style asm statement is recognized by having a BOL token preceding it. */
iasm_stmt: IASM_BOL iasm_save_location iasm_stmt_list IASM_EOL
{ $$ = NULL_TREE; }
;
/* (in 4.2 ay) */
iasm_stmt_nobol: iasm_save_location iasm_stmt_list IASM_EOL
{
$$ = NULL_TREE;
iasm_state = iasm_none;
iasm_at_bol = false;
}
;
/* (in 4.2 ap) */
/* A single line may have multiple statements separated by ';'. */
iasm_stmt_list:
/* empty */
| single_iasm_stmt
{}
| iasm_stmt_list ';' iasm_maybe_comment single_iasm_stmt
| iasm_stmt_list ';' iasm_maybe_comment
| iasm_stmt_list ASM_KEYWORD
| iasm_stmt_list ASM_KEYWORD single_iasm_stmt
;
/* (in 4.2 ao) */
iasm_maybe_comment:
{
if (flag_ms_asms)
{
iasm_skip_to_eol ();
yychar = YYEMPTY;
}
}
;
/* (in 4.2 aq) */
iasm_identifier:
iasm_identifier1 ' '
{ $$ = $1; }
| iasm_identifier1
{ $$ = $1; iasm_split_next = 0; }
;
/* (in 4.2 aq) */
iasm_identifier1:
identifier
{
if (iasm_split_next &&
(yychar == '.'
|| yychar == '+'
|| yychar == '-'))
{
iasm_insert_saved_token ();
yychar = ' ';
}
}
| iasm_identifier1 '.'
{ $$ = iasm_get_identifier ($1, "."); }
| iasm_identifier1 '+'
{ $$ = iasm_get_identifier ($1, "+"); }
| iasm_identifier1 '-'
{ $$ = iasm_get_identifier ($1, "-"); }
| '.' identifier
{ $$ = prepend_char_identifier ($2, '.'); }
;
/* (in 4.2 an) */
iasm_maybe_prefix:
iasm_identifier
{ $$ = c_parse_iasm_maybe_prefix ($1); }
;
/* (in 4.2 ar) */
/* A single statement consists of one or more labels (identified by a
leading '@' and/or a trailing ':'), optionally followed by opcode
and operands. */
single_iasm_stmt:
iasm_maybe_prefix
{ iasm_in_operands = true; }
iasm_operands
{ $$ = iasm_stmt ($1, $3, iasm_lineno); }
| identifier STATIC iasm_operand
{ $$ = iasm_entry ($1, $2, $3.value); }
| identifier SCSPEC iasm_operand
{ $$ = iasm_entry ($1, $2, $3.value); }
| iasm_label
{}
| iasm_label single_iasm_stmt
{}
;
/* (in 4.2 ar) */
iasm_label:
identifier ':'
{ iasm_label ($1, 0); }
| '@' identifier
{ iasm_label ($2, 1); }
| '@' identifier ':'
{ iasm_label ($2, 1); }
| '@' CONSTANT
{ iasm_label ($2, 1); }
| '@' CONSTANT ':'
{ iasm_label ($2, 1); }
;
/* (in 4.2 au) */
iasm_stmts:
stmt
{}
| iasm_stmts stmt
{}
;
/* (in 4.2 as) */
/* (in 4.2 at) */
/* An asm block within a function is simpler than asm functions; no
declarations are possible, so we switch to the block interior state
immediately. */
iasm_compstmt_start: ASM_KEYWORD '{'
{
if (flag_iasm_blocks)
{
iasm_state = iasm_asm;
inside_iasm_block = true;
iasm_at_bol = true;
iasm_clear_labels ();
}
else
/* This will probably choke badly... */
error ("asm blocks not enabled, use `-fasm-blocks'");
$$ = c_begin_compound_stmt (true);
}
;
iasm_compstmt: ASM_KEYWORD
{
if (flag_iasm_blocks)
{
iasm_state = iasm_asm;
inside_iasm_block = true;
iasm_clear_labels ();
if (yychar == ';' && flag_ms_asms)
{
iasm_skip_to_eol ();
yychar = YYEMPTY;
}
yychar = IASM_SEE_OPCODE (yychar, yylval.ttype);
}
else
/* This will probably choke badly... */
error ("asm blocks not enabled, use `-fasm-blocks'");
$<ttype>$ = c_begin_compound_stmt (true);
}
iasm_stmt_nobol
{
$$ = c_finish_expr_stmt ($3);
iasm_end_block ();
$<ttype>$ = c_end_compound_stmt ($<ttype>2, true);
}
;
/* (in 4.2 aw) */
iasm_compstmt_nostart:
'}'
| iasm_compstmt_contents_nonempty '}'
{
iasm_end_block ();
}
;
/* (in 4.2 au) */
iasm_compstmt_contents_nonempty:
iasm_stmts
| error
;
/* (in 4.2 av) */
iasm_compstmt: iasm_compstmt_start iasm_compstmt_nostart
{ $$ = c_end_compound_stmt ($1, true); }
;
/* (in 4.2 az) */
iasm_operands:
/* empty */
{ $$ = NULL_TREE; }
| iasm_nonnull_operands
;
/* (in 4.2 az) */
iasm_nonnull_operands:
iasm_operand
{ $$ = build_tree_list (NULL_TREE, $1.value); }
| iasm_nonnull_operands ',' iasm_operand
{ $$ = chainon ($1, build_tree_list (NULL_TREE, $3.value)); }
;
/* Alternatively this could go to the regular expr_no_commas, but then
all the semantic actions would need to be tweaked to handle the
possibility of CW asm coming through. For example, "offset(reg)"
would be handled by function call code (bleah). */
iasm_operand: iasm_expr_no_commas
| iasm_operand '(' iasm_expr_no_commas ')'
{ $$.value = iasm_build_register_offset ($1.value, $3.value);
$$.original_code = ERROR_MARK; }
;
/* APPLE LOCAL end CW asm blocks */
/* The forced readahead in here is because we might be at the end of a
line, and the line and file won't be bumped until yylex absorbs the
first token on the next line. */
save_location:
{ if (yychar == YYEMPTY)
yychar = YYLEX;
$$ = input_location; }
;
lineno_labels:
/* empty */
| lineno_labels lineno_label
;
/* A labeled statement. In C99 it also generates an implicit block. */
c99_block_lineno_labeled_stmt:
c99_block_start lineno_labels lineno_stmt
/* APPLE LOCAL begin radar 4502236 */
{ $$ = c_end_compound_stmt ($1,
flag_isoc99
|| (c_dialect_objc() && objc_foreach_context)); }
/* APPLE LOCAL end radar 4502236 */
;
lineno_stmt:
save_location stmt
{
/* Two cases cannot and do not have line numbers associated:
If stmt is degenerate, such as "2;", then stmt is an
INTEGER_CST, which cannot hold line numbers. But that's
ok because the statement will either be changed to a
MODIFY_EXPR during gimplification of the statement expr,
or discarded. If stmt was compound, but without new
variables, we will have skipped the creation of a BIND
and will have a bare STATEMENT_LIST. But that's ok
because (recursively) all of the component statments
should already have line numbers assigned. */
if ($2 && EXPR_P ($2))
SET_EXPR_LOCATION ($2, $1);
}
;
lineno_label:
save_location label
{ if ($2) SET_EXPR_LOCATION ($2, $1); }
;
condition: save_location expr
{ $$ = lang_hooks.truthvalue_conversion ($2.value);
if (EXPR_P ($$))
SET_EXPR_LOCATION ($$, $1); }
;
/* Implement -Wparenthesis by special casing IF statement directly nested
within IF statement. This requires some amount of duplication of the
productions under c99_block_lineno_labeled_stmt in order to work out.
But it's still likely more maintainable than lots of state outside the
parser... */
if_statement_1:
c99_block_start lineno_labels if_statement
{ $$ = c_end_compound_stmt ($1, flag_isoc99); }
;
if_statement_2:
c99_block_start lineno_labels ';'
{ if (extra_warnings)
add_stmt (build (NOP_EXPR, NULL_TREE, NULL_TREE));
$$ = c_end_compound_stmt ($1, flag_isoc99); }
| c99_block_lineno_labeled_stmt
;
if_statement:
IF c99_block_start save_location '(' condition ')'
if_statement_1 ELSE if_statement_2
{ c_finish_if_stmt ($3, $5, $7, $9, true);
add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
| IF c99_block_start save_location '(' condition ')'
if_statement_2 ELSE if_statement_2
{ c_finish_if_stmt ($3, $5, $7, $9, false);
add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
| IF c99_block_start save_location '(' condition ')'
if_statement_1 %prec IF
{ c_finish_if_stmt ($3, $5, $7, NULL, true);
add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
| IF c99_block_start save_location '(' condition ')'
if_statement_2 %prec IF
{ c_finish_if_stmt ($3, $5, $7, NULL, false);
add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
;
start_break: /* empty */
{ $$ = c_break_label; c_break_label = NULL; }
;
start_continue: /* empty */
{ $$ = c_cont_label; c_cont_label = NULL; }
;
while_statement:
WHILE c99_block_start save_location '(' condition ')'
start_break start_continue c99_block_lineno_labeled_stmt
{ c_finish_loop ($3, $5, NULL, $9, c_break_label,
c_cont_label, true);
add_stmt (c_end_compound_stmt ($2, flag_isoc99));
c_break_label = $7; c_cont_label = $8; }
;
do_statement:
DO c99_block_start save_location start_break start_continue
c99_block_lineno_labeled_stmt WHILE
{ $<ttype>$ = c_break_label; c_break_label = $4; }
{ $<ttype>$ = c_cont_label; c_cont_label = $5; }
'(' condition ')' ';'
{ c_finish_loop ($3, $11, NULL, $6, $<ttype>8,
$<ttype>9, false);
add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
;
xexpr:
/* empty */
{ $$ = NULL_TREE; }
| expr
{ $$ = $1.value; }
;
/* APPLE LOCAL begin C* language (in 4.2 aj) */
for_init_stmt:
xexpr ';'
{ objc_foreach_context = 0; c_finish_expr_stmt ($1); }
| decl
{ objc_foreach_context = 0; check_for_loop_decls (); }
;
/* APPLE LOCAL end C* language (in 4.2 aj) */
for_cond_expr: save_location xexpr
{ if ($2)
{
$$ = lang_hooks.truthvalue_conversion ($2);
if (EXPR_P ($$))
SET_EXPR_LOCATION ($$, $1);
}
else
$$ = NULL;
}
;
for_incr_expr: xexpr
{ $$ = c_process_expr_stmt ($1); }
;
/* APPLE LOCAL begin C* language */
@@ifobjc
for_objc_collection:
declspecs_ts setspecs declarator maybeasm maybe_attribute AT_IN
{ objc_foreach_context = 0;
$<ttype>$ = start_decl ($3, current_declspecs, true,
chainon ($5, all_prefix_attributes));
if (!$<ttype>$)
$<ttype>$ = error_mark_node;
start_init ($<ttype>$, $4, global_bindings_p ()); }
init
/* APPLE LOCAL begin radar 4472881 */
{ int save_flag_isoc99 = flag_isoc99;
finish_init ();
$$ = build_tree_list ($<ttype>7, $8.value);
POP_DECLSPEC_STACK;
flag_isoc99 = 1;
check_for_loop_decls ();
flag_isoc99 = save_flag_isoc99;
}
/* APPLE LOCAL end radar 4472881 */
| expr AT_IN init
{
/* APPLE LOCAL radar 4550582 */
objc_foreach_context = 0;
$$ = build_tree_list ($1.value, $3.value);
}
;
@@end_ifobjc
/* APPLE LOCAL radar 4472881 (in 4.2 u) */
for_keyword: FOR
{objc_foreach_context = 1;}
;
for_statement:
for_keyword c99_block_start '(' for_init_stmt
/* APPLE LOCAL end C* language */
save_location for_cond_expr ';' for_incr_expr ')'
start_break start_continue c99_block_lineno_labeled_stmt
{ c_finish_loop ($5, $6, $8, $12, c_break_label,
c_cont_label, true);
/* APPLE LOCAL radar 4472881 (in 4.2 ai) */
add_stmt (c_end_compound_stmt ($2, flag_isoc99 || c_dialect_objc ()));
c_break_label = $10; c_cont_label = $11; }
/* APPLE LOCAL begin C* language */
@@ifobjc
| for_keyword c99_block_start '(' for_objc_collection save_location ')'
start_break start_continue c99_block_lineno_labeled_stmt
{ objc_finish_foreach_loop ($5, $4, $9, c_break_label, c_cont_label);
/* APPLE LOCAL radar 4472881 */
add_stmt (c_end_compound_stmt ($2, 1));
c_break_label = $7; c_cont_label = $8;
}
@@end_ifobjc
;
/* APPLE LOCAL end C* language */
switch_statement:
SWITCH c99_block_start '(' expr ')'
{ $<ttype>$ = c_start_case ($4.value); }
start_break c99_block_lineno_labeled_stmt
{ c_finish_case ($8);
if (c_break_label)
add_stmt (build (LABEL_EXPR, void_type_node,
c_break_label));
c_break_label = $7;
add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
;
/* Parse a single real statement, not including any labels or compounds. */
stmt_nocomp:
expr ';'
{ $$ = c_finish_expr_stmt ($1.value); }
| if_statement
{ $$ = NULL_TREE; }
| while_statement
{ $$ = NULL_TREE; }
| do_statement
{ $$ = NULL_TREE; }
| for_statement
{ $$ = NULL_TREE; }
| switch_statement
{ $$ = NULL_TREE; }
/* APPLE LOCAL begin CW asm blocks */
/* (in 4.2 as) */
| iasm_compstmt
{ $$ = c_finish_expr_stmt ($1); }
| iasm_stmt
{ $$ = c_finish_expr_stmt ($1); }
/* APPLE LOCAL end CW asm blocks */
| BREAK ';'
{ $$ = c_finish_bc_stmt (&c_break_label, true); }
| CONTINUE ';'
{ $$ = c_finish_bc_stmt (&c_cont_label, false); }
| RETURN ';'
{ $$ = c_finish_return (NULL_TREE); }
| RETURN expr ';'
{ $$ = c_finish_return ($2.value); }
| asm_stmt
| GOTO identifier ';'
{ $$ = c_finish_goto_label ($2); }
| GOTO '*' expr ';'
{ $$ = c_finish_goto_ptr ($3.value); }
| ';'
{ $$ = NULL_TREE; }
@@ifobjc
| AT_THROW expr ';'
{ $$ = objc_build_throw_stmt ($2.value); }
| AT_THROW ';'
{ $$ = objc_build_throw_stmt (NULL_TREE); }
| objc_try_catch_stmt
{ $$ = NULL_TREE; }
| AT_SYNCHRONIZED save_location '(' expr ')' compstmt
{ objc_build_synchronized ($2, $4.value, $6); $$ = NULL_TREE; }
;
/* APPLE LOCAL begin radar 2848255 */
objc_catch_parm:
parm
{ $$ = $1; }
| ELLIPSIS
{ $$ = NULL_TREE; }
;
objc_catch_prefix:
AT_CATCH '(' objc_catch_parm ')'
{ objc_begin_catch_clause ($3 == NULL_TREE
? NULL_TREE
: grokparm ($3)); }
;
/* APPLE LOCAL end radar 2848255 */
objc_catch_clause:
objc_catch_prefix '{' compstmt_nostart
{ objc_finish_catch_clause (); }
| objc_catch_prefix '{' error '}'
{ objc_finish_catch_clause (); }
;
objc_opt_catch_list:
/* empty */
| objc_opt_catch_list objc_catch_clause
;
objc_try_catch_clause:
AT_TRY save_location compstmt
{ objc_begin_try_stmt ($2, $3); }
objc_opt_catch_list
;
objc_finally_clause:
AT_FINALLY save_location compstmt
{ objc_build_finally_clause ($2, $3); }
;
objc_try_catch_stmt:
objc_try_catch_clause
{ objc_finish_try_stmt (); }
| objc_try_catch_clause objc_finally_clause
{ objc_finish_try_stmt (); }
@@end_ifobjc
;
/* Parse a single or compound real statement, not including any labels. */
stmt:
compstmt
{ add_stmt ($1); $$ = NULL_TREE; }
| stmt_nocomp
;
/* Any kind of label, including jump labels and case labels.
ANSI C accepts labels only before statements, but we allow them
also at the end of a compound statement. */
label: CASE expr_no_commas ':'
{ $$ = do_case ($2.value, NULL_TREE); }
| CASE expr_no_commas ELLIPSIS expr_no_commas ':'
{ $$ = do_case ($2.value, $4.value); }
| DEFAULT ':'
{ $$ = do_case (NULL_TREE, NULL_TREE); }
| identifier save_location ':' maybe_attribute
{ tree label = define_label ($2, $1);
if (label)
{
decl_attributes (&label, $4, 0);
$$ = add_stmt (build_stmt (LABEL_EXPR, label));
}
else
$$ = NULL_TREE;
}
;
/* Asm expressions and statements */
/* simple_asm_expr is used in restricted contexts, where a full
expression with inputs and outputs does not make sense. */
simple_asm_expr:
ASM_KEYWORD stop_string_translation
'(' asm_string ')' start_string_translation
{ $$ = $4; }
;
/* maybeasm: used for assembly names for declarations */
maybeasm:
/* empty */
{ $$ = NULL_TREE; }
| simple_asm_expr
;
/* asmdef: asm() outside a function body. */
asmdef:
simple_asm_expr ';'
{ assemble_asm ($1); }
| ASM_KEYWORD error start_string_translation ';'
{}
;
/* Full-blown asm statement with inputs, outputs, clobbers, and
volatile tag allowed. */
asm_stmt:
ASM_KEYWORD maybe_volatile stop_string_translation
'(' asm_argument ')' start_string_translation ';'
{ $$ = build_asm_stmt ($2, $5); }
;
asm_argument:
/* no operands */
asm_string
{ $$ = build_asm_expr ($1, 0, 0, 0, true); }
/* output operands */
| asm_string ':' asm_operands
{ $$ = build_asm_expr ($1, $3, 0, 0, false); }
/* output and input operands */
| asm_string ':' asm_operands ':' asm_operands
{ $$ = build_asm_expr ($1, $3, $5, 0, false); }
/* output and input operands and clobbers */
| asm_string ':' asm_operands ':' asm_operands ':' asm_clobbers
{ $$ = build_asm_expr ($1, $3, $5, $7, false); }
;
/* Either 'volatile' or nothing. First thing in an `asm' statement. */
maybe_volatile:
/* empty */
{ $$ = 0; }
| TYPE_QUAL
{ if ($1 != ridpointers[RID_VOLATILE])
{
warning ("%E qualifier ignored on asm", $1);
$$ = 0;
}
else
$$ = $1;
}
;
/* These are the operands other than the first string and colon
in asm ("addextend %2,%1": "=dm" (x), "0" (y), "g" (*x)) */
asm_operands: /* empty */
{ $$ = NULL_TREE; }
| nonnull_asm_operands
;
nonnull_asm_operands:
asm_operand
| nonnull_asm_operands ',' asm_operand
{ $$ = chainon ($1, $3); }
;
asm_operand:
asm_string start_string_translation '(' expr ')'
stop_string_translation
{ $$ = build_tree_list (build_tree_list (NULL_TREE, $1),
$4.value); }
| '[' identifier ']' asm_string start_string_translation
'(' expr ')' stop_string_translation
{ $2 = build_string (IDENTIFIER_LENGTH ($2),
IDENTIFIER_POINTER ($2));
$$ = build_tree_list (build_tree_list ($2, $4), $7.value); }
;
asm_clobbers:
asm_string
{ $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
| asm_clobbers ',' asm_string
{ $$ = tree_cons (NULL_TREE, $3, $1); }
;
/* Strings in 'asm' must be narrow strings. */
asm_string:
STRING
{ if (TYPE_MAIN_VARIANT (TREE_TYPE (TREE_TYPE ($1)))
!= char_type_node)
{
error ("wide string literal in %<asm%>");
$$ = build_string (1, "");
}
else
$$ = $1; }
;
stop_string_translation:
{ c_lex_string_translate = 0; }
;
start_string_translation:
{ c_lex_string_translate = 1; }
;
/* APPLE LOCAL begin CW asm blocks */
iasm_expr_no_commas:
iasm_unary_expr
| iasm_expr_no_commas '+' iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas '-' iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas '*' iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas '/' iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas '%' iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas LSHIFT iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas RSHIFT iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas ARITHCOMPARE iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas EQCOMPARE iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas '&' iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas '|' iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas '^' iasm_expr_no_commas
{ $$ = parser_build_binary_op ($2, $1, $3); }
| iasm_expr_no_commas ANDAND
{ $1.value = c_common_truthvalue_conversion
(default_conversion ($1.value));
skip_evaluation += $1.value == boolean_false_node; }
iasm_expr_no_commas
{ skip_evaluation -= $1.value == boolean_false_node;
$$ = parser_build_binary_op (TRUTH_ANDIF_EXPR, $1, $4); }
| iasm_expr_no_commas OROR
{ $1.value = c_common_truthvalue_conversion
(default_conversion ($1.value));
skip_evaluation += $1.value == boolean_true_node; }
iasm_expr_no_commas
{ skip_evaluation -= $1.value == boolean_true_node;
$$ = parser_build_binary_op (TRUTH_ORIF_EXPR, $1, $4); }
;
iasm_unary_expr:
iasm_primary
/* (in 4.2 bb) */
| iasm_primary IDENTIFIER iasm_unary_expr
{
/* Handle things like: inc dword ptr [eax] */
if (strcasecmp (IDENTIFIER_POINTER ($2), "ptr") != 0)
error ("expected %<ptr%>");
$$.value = iasm_ptr_conv ($1.value, $3.value);
$$.original_code = ERROR_MARK;
}
| '*' iasm_unary_expr %prec UNARY
{ $$.value = build_indirect_ref ($2.value, "unary *");
$$.original_code = ERROR_MARK; }
| unop iasm_unary_expr %prec UNARY
{
if (TREE_CODE ($2.value) == COMPOUND_EXPR)
{
tree neg = build_unary_op ($1, TREE_OPERAND ($2.value, 0), 0);
tree reg = TREE_OPERAND ($2.value, 1);
$$.value = iasm_build_register_offset (neg, reg);
}
else
{
/* (in 4.2 bc) */
if (TREE_CODE ($2.value) == LABEL_DECL
&& $1 == ADDR_EXPR)
$$.value = finish_label_address_expr (DECL_NAME ($2.value));
else
$$.value = build_unary_op ($1, $2.value, 0);
overflow_warning ($$.value);
}
$$.original_code = ERROR_MARK;
}
| sizeof iasm_unary_expr %prec UNARY
{ skip_evaluation--;
if (TREE_CODE ($2.value) == COMPONENT_REF
&& DECL_C_BIT_FIELD (TREE_OPERAND ($2.value, 1)))
error ("`sizeof' applied to a bit-field");
else if (TREE_CODE ($2.value) == IDENTIFIER_NODE)
{
undeclared_variable ($2.value);
$2.value = error_mark_node;
}
$$.value = c_sizeof (TREE_TYPE ($2.value));
$$.original_code = ERROR_MARK; }
| sizeof '(' typename ')' %prec HYPERUNARY
{ skip_evaluation--;
$$.value = c_sizeof (groktypename ($3));
$$.original_code = ERROR_MARK; }
| alignof iasm_unary_expr %prec UNARY
{ skip_evaluation--;
$$.value = c_alignof_expr ($2.value);
$$.original_code = ERROR_MARK; }
| alignof '(' typename ')' %prec HYPERUNARY
{ skip_evaluation--;
$$.value = c_alignof (groktypename ($3));
$$.original_code = ERROR_MARK; }
;
iasm_primary:
IDENTIFIER
{
if (yychar == YYEMPTY)
yychar = YYLEX;
$$.value = build_external_ref ($1, yychar == '(');
$$.original_code = ERROR_MARK;
}
| '@' IDENTIFIER
{
tree atsignid = prepend_char_identifier ($2, '@');
if (yychar == YYEMPTY)
yychar = YYLEX;
$$.value = build_external_ref (atsignid, yychar == '(');
$$.original_code = ERROR_MARK;
}
| CONSTANT
{ $$.value = $1; $$.original_code = ERROR_MARK; }
| STRING
{ $$.value = $1; $$.original_code = STRING_CST; }
| '(' iasm_expr_no_commas ')'
{ char class = TREE_CODE_CLASS (TREE_CODE ($2.value));
if (IS_EXPR_CODE_CLASS (class))
$2.original_code = ERROR_MARK;
$$ = $2; }
| '(' error ')'
{ $$.value = error_mark_node; $$.original_code = ERROR_MARK; }
| iasm_primary '[' iasm_expr_no_commas ']' %prec '.'
{ $$.value = build_array_ref ($1.value, $3.value);
$$.original_code = ERROR_MARK; }
| '[' iasm_expr_no_commas ']' %prec '.'
{ $$.value = iasm_build_bracket ($2.value, NULL_TREE);
$$.original_code = ERROR_MARK; }
| TYPENAME '.' identifier
{ $$.value = iasm_c_build_component_ref ($1, $3);
$$.original_code = ERROR_MARK; }
| iasm_primary '.' identifier
{ $$.value = iasm_c_build_component_ref ($1.value, $3);
$$.original_code = ERROR_MARK; }
/* (in 4.2 bc) */
| iasm_primary '.' CONSTANT
{ /* We allow [eax].16 to refer to [eax + 16]. */
$$.value = iasm_c_build_component_ref ($1.value, $3);
$$.original_code = ERROR_MARK; }
| iasm_primary POINTSAT identifier
{
tree expr = build_indirect_ref ($1.value, "->");
$$.value = build_component_ref (expr, $3);
$$.original_code = ERROR_MARK;
}
/* (in 4.2 ba) */
| '.'
{
$$.value = get_identifier (".");;
$$.original_code = ERROR_MARK;
}
;
/* APPLE LOCAL end CW asm blocks */
/* This is what appears inside the parens in a function declarator.
Its value is a list of ..._TYPE nodes. Attributes must appear here
to avoid a conflict with their appearance after an open parenthesis
in an abstract declarator, as in
"void bar (int (__attribute__((__mode__(SI))) int foo));". */
parmlist:
maybe_attribute
{ push_scope ();
declare_parm_level (); }
parmlist_1
{ $$ = $3;
pop_scope (); }
;
parmlist_1:
parmlist_2 ')'
| parms ';'
{ mark_forward_parm_decls (); }
maybe_attribute
{ /* Dummy action so attributes are in known place
on parser stack. */ }
parmlist_1
{ $$ = $6; }
| error ')'
{ $$ = XOBNEW (&parser_obstack, struct c_arg_info);
$$->parms = 0;
$$->tags = 0;
$$->types = 0;
/* APPLE LOCAL mainline 2006-05-19 4336222 */
$$->had_vla_unspec = 0;
$$->others = 0; }
;
/* This is what appears inside the parens in a function declarator.
Its value is represented in the format that grokdeclarator expects. */
parmlist_2: /* empty */
{ $$ = XOBNEW (&parser_obstack, struct c_arg_info);
$$->parms = 0;
$$->tags = 0;
$$->types = 0;
/* APPLE LOCAL mainline 2006-05-19 4336222 */
$$->had_vla_unspec = 0;
$$->others = 0; }
| ELLIPSIS
{ $$ = XOBNEW (&parser_obstack, struct c_arg_info);
$$->parms = 0;
$$->tags = 0;
$$->others = 0;
/* APPLE LOCAL mainline 2006-05-19 4336222 */
$$->had_vla_unspec = 0;
/* Suppress -Wold-style-definition for this case. */
$$->types = error_mark_node;
error ("ISO C requires a named argument before %<...%>");
}
| parms
{ $$ = get_parm_info (/*ellipsis=*/false); }
| parms ',' ELLIPSIS
{ $$ = get_parm_info (/*ellipsis=*/true); }
;
parms:
firstparm
{ push_parm_decl ($1); }
| parms ',' parm
{ push_parm_decl ($3); }
;
/* A single parameter declaration or parameter type name,
as found in a parmlist. */
parm:
declspecs_ts setspecs parm_declarator maybe_attribute
{ $$ = build_c_parm (current_declspecs,
chainon ($4, all_prefix_attributes), $3);
POP_DECLSPEC_STACK; }
| declspecs_ts setspecs notype_declarator maybe_attribute
{ $$ = build_c_parm (current_declspecs,
chainon ($4, all_prefix_attributes), $3);
POP_DECLSPEC_STACK; }
| declspecs_ts setspecs absdcl_maybe_attribute
{ $$ = $3;
POP_DECLSPEC_STACK; }
| declspecs_nots setspecs notype_declarator maybe_attribute
{ $$ = build_c_parm (current_declspecs,
chainon ($4, all_prefix_attributes), $3);
POP_DECLSPEC_STACK; }
| declspecs_nots setspecs absdcl_maybe_attribute
{ $$ = $3;
POP_DECLSPEC_STACK; }
;
/* The first parm, which must suck attributes from off the top of the parser
stack. */
firstparm:
declspecs_ts_nosa setspecs_fp parm_declarator maybe_attribute
{ $$ = build_c_parm (current_declspecs,
chainon ($4, all_prefix_attributes), $3);
POP_DECLSPEC_STACK; }
| declspecs_ts_nosa setspecs_fp notype_declarator maybe_attribute
{ $$ = build_c_parm (current_declspecs,
chainon ($4, all_prefix_attributes), $3);
POP_DECLSPEC_STACK; }
| declspecs_ts_nosa setspecs_fp absdcl_maybe_attribute
{ $$ = $3;
POP_DECLSPEC_STACK; }
| declspecs_nots_nosa setspecs_fp notype_declarator maybe_attribute
{ $$ = build_c_parm (current_declspecs,
chainon ($4, all_prefix_attributes), $3);
POP_DECLSPEC_STACK; }
| declspecs_nots_nosa setspecs_fp absdcl_maybe_attribute
{ $$ = $3;
POP_DECLSPEC_STACK; }
;
setspecs_fp:
setspecs
{ prefix_attributes = chainon (prefix_attributes, $<ttype>-2);
all_prefix_attributes = prefix_attributes; }
;
/* This is used in a function definition
where either a parmlist or an identifier list is ok.
Its value is a list of ..._TYPE nodes or a list of identifiers. */
parmlist_or_identifiers:
maybe_attribute
{ push_scope ();
declare_parm_level (); }
parmlist_or_identifiers_1
{ $$ = $3;
pop_scope (); }
;
parmlist_or_identifiers_1:
parmlist_1
| identifiers ')'
{ $$ = XOBNEW (&parser_obstack, struct c_arg_info);
$$->parms = 0;
$$->tags = 0;
$$->types = $1;
$$->others = 0;
/* APPLE LOCAL mainline 2006-05-19 4336222 */
$$->had_vla_unspec = 0;
/* Make sure we have a parmlist after attributes. */
if ($<ttype>-1 != 0)
YYERROR1;
}
;
/* A nonempty list of identifiers. */
identifiers:
IDENTIFIER
{ $$ = build_tree_list (NULL_TREE, $1); }
| identifiers ',' IDENTIFIER
{ $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
;
/* A nonempty list of identifiers, including typenames. */
identifiers_or_typenames:
identifier
{ $$ = build_tree_list (NULL_TREE, $1); }
| identifiers_or_typenames ',' identifier
{ $$ = chainon ($1, build_tree_list (NULL_TREE, $3)); }
;