OSDN Git Service

* g++.dg/abi/vague1.C: Use xfail, rather than embedded Tcl code.
[pf3gnuchains/gcc-fork.git] / gcc / c-parse.in
index 30f2551..477ae62 100644 (file)
@@ -1,23 +1,23 @@
 /* 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 Free Software Foundation, Inc.
+   1997, 1998, 1999, 2000, 2001, 2002, 2003 Free Software Foundation, Inc.
 
-This file is part of GNU CC.
+This file is part of GCC.
 
-GNU CC 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 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.
 
-GNU CC 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.
+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 GNU CC; see the file COPYING.  If not, write to
-the Free Software Foundation, 59 Temple Place - Suite 330,
-Boston, MA 02111-1307, USA.  */
+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.
@@ -28,30 +28,28 @@ Boston, MA 02111-1307, USA.  */
 /* To whomever it may concern: I have heard that such a thing was once
    written by AT&T, but I have never seen it.  */
 
-ifobjc
-%expect 74
-end ifobjc
 ifc
-%expect 53
+%expect 10 /* shift/reduce conflicts, and no reduce/reduce conflicts.  */
 end ifc
 
 %{
 #include "config.h"
 #include "system.h"
-#include <setjmp.h>
+#include "coretypes.h"
+#include "tm.h"
 #include "tree.h"
 #include "input.h"
 #include "cpplib.h"
 #include "intl.h"
 #include "timevar.h"
-#include "c-lex.h"
+#include "c-pragma.h"          /* For YYDEBUG definition, and parse_in.  */
 #include "c-tree.h"
-#include "c-pragma.h"
 #include "flags.h"
+#include "varray.h"
 #include "output.h"
 #include "toplev.h"
 #include "ggc.h"
-  
+
 #ifdef MULTIBYTE_CHARS
 #include <locale.h>
 #endif
@@ -60,23 +58,51 @@ ifobjc
 #include "objc-act.h"
 end ifobjc
 
-/* Since parsers are distinct for each language, put the language string
-   definition here.  */
-ifobjc
-const char * const language_string = "GNU Objective-C";
-end ifobjc
-ifc
-const char * const language_string = "GNU C";
-end ifc
-
 /* Like YYERROR but do call yyerror.  */
 #define YYERROR1 { yyerror ("syntax error"); YYERROR; }
 
-/* Cause the "yydebug" variable to be defined.  */
-#define YYDEBUG 1
-
-/* Rename the "yyparse" function so that we can override it elsewhere.  */
-#define yyparse yyparse_1
+/* 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 = (short *)                                                        \
+       really_call_realloc (*(SS), newsize * sizeof (short));          \
+      newvs = (YYSTYPE *)                                              \
+       really_call_realloc (*(VS), newsize * sizeof (YYSTYPE));        \
+    }                                                                  \
+  else                                                                 \
+    {                                                                  \
+      newss = (short *) really_call_malloc (newsize * sizeof (short)); \
+      newvs = (YYSTYPE *) 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
@@ -95,7 +121,8 @@ end ifc
 
 /* Reserved words that specify storage class.
    yylval contains an IDENTIFIER_NODE which indicates which one.  */
-%token SCSPEC
+%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.  */
@@ -111,6 +138,7 @@ end ifc
 
 /* String constants in raw form.
    yylval is a STRING_CST node.  */
+
 %token STRING
 
 /* "...", used for functions with variable arglists.  */
@@ -121,9 +149,12 @@ end ifc
 %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
+%token REALPART IMAGPART VA_ARG CHOOSE_EXPR TYPES_COMPATIBLE_P
 %token PTR_VALUE PTR_BASE PTR_EXTENT
 
+/* function name can be a string const or a var decl. */
+%token STRING_FUNC_NAME VAR_FUNC_NAME
+
 /* Add precedence rules to solve dangling else s/r conflict */
 %nonassoc IF
 %nonassoc ELSE
@@ -153,23 +184,28 @@ end ifc
 %token INTERFACE IMPLEMENTATION END SELECTOR DEFS ENCODE
 %token CLASSNAME PUBLIC PRIVATE PROTECTED PROTOCOL OBJECTNAME CLASS ALIAS
 
-/* Objective-C string constants in raw form.
-   yylval is an STRING_CST node.  */
-%token OBJC_STRING
-
-
 %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 expr nonnull_exprlist exprlist
-%type <ttype> expr_no_commas cast_expr unary_expr primary string STRING
-%type <ttype> typed_declspecs reserved_declspecs
-%type <ttype> typed_typespecs reserved_typespecquals
-%type <ttype> declmods typespec typespecqual_reserved
-%type <ttype> typed_declspecs_no_prefix_attr reserved_declspecs_no_prefix_attr
-%type <ttype> declmods_no_prefix_attr
-%type <ttype> SCSPEC TYPESPEC TYPE_QUAL nonempty_type_quals maybe_type_qual
+%type <ttype> expr_no_commas cast_expr unary_expr primary STRING
+%type <ttype> declspecs_nosc_nots_nosa_noea declspecs_nosc_nots_nosa_ea
+%type <ttype> declspecs_nosc_nots_sa_noea declspecs_nosc_nots_sa_ea
+%type <ttype> declspecs_nosc_ts_nosa_noea declspecs_nosc_ts_nosa_ea
+%type <ttype> declspecs_nosc_ts_sa_noea declspecs_nosc_ts_sa_ea
+%type <ttype> declspecs_sc_nots_nosa_noea declspecs_sc_nots_nosa_ea
+%type <ttype> declspecs_sc_nots_sa_noea declspecs_sc_nots_sa_ea
+%type <ttype> declspecs_sc_ts_nosa_noea declspecs_sc_ts_nosa_ea
+%type <ttype> declspecs_sc_ts_sa_noea declspecs_sc_ts_sa_ea
+%type <ttype> declspecs_ts declspecs_nots
+%type <ttype> declspecs_ts_nosa declspecs_nots_nosa
+%type <ttype> declspecs_nosc_ts declspecs_nosc_nots declspecs_nosc declspecs
+%type <ttype> maybe_type_quals_attrs typespec_nonattr typespec_attr
+%type <ttype> typespec_reserved_nonattr typespec_reserved_attr
+%type <ttype> typespec_nonreserved_nonattr
+
+%type <ttype> scspec SCSPEC STATIC TYPESPEC TYPE_QUAL maybe_type_qual
 %type <ttype> initdecls notype_initdecls initdcl notype_initdcl
 %type <ttype> init maybeasm
 %type <ttype> asm_operands nonnull_asm_operands asm_operand asm_clobbers
@@ -183,19 +219,24 @@ end ifc
 %type <ttype> declarator
 %type <ttype> notype_declarator after_type_declarator
 %type <ttype> parm_declarator
+%type <ttype> parm_declarator_starttypename parm_declarator_nostarttypename
+%type <ttype> array_declarator
 
-%type <ttype> structsp component_decl_list component_decl_list2
-%type <ttype> component_decl components component_declarator
+%type <ttype> 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 <ttype> typename absdcl absdcl1 type_quals
-%type <ttype> xexpr parms parm identifiers
+%type <ttype> typename absdcl absdcl1 absdcl1_ea absdcl1_noea
+%type <ttype> direct_absdcl1 absdcl_maybe_attribute
+%type <ttype> xexpr parms parm firstparm identifiers
 
 %type <ttype> parmlist parmlist_1 parmlist_2
 %type <ttype> parmlist_or_identifiers parmlist_or_identifiers_1
 %type <ttype> identifiers_or_typenames
 
-%type <itype> setspecs
+%type <itype> setspecs setspecs_fp
 
 %type <filename> save_filename
 %type <lineno> save_lineno
@@ -211,76 +252,105 @@ ifobjc
 %type <ttype> selectorarg keywordnamelist keywordname objcencodeexpr
 %type <ttype> objc_string non_empty_protocolrefs protocolrefs identifier_list objcprotocolexpr
 
-%type <ttype> CLASSNAME OBJC_STRING OBJECTNAME
+%type <ttype> CLASSNAME OBJECTNAME
 end ifobjc
 \f
 %{
-/* Number of statements (loosely speaking) and compound statements 
+/* Number of statements (loosely speaking) and compound statements
    seen so far.  */
 static int stmt_count;
 static int compstmt_count;
-  
-/* Input file and line number of the end of the body of last simple_if;
+
+/* Input location of the end of the body of last simple_if;
    used by the stmt-rule immediately after simple_if returns.  */
-static const char *if_stmt_file;
-static int if_stmt_line;
+static location_t if_stmt_locus;
+
 
 /* List of types and structure classes of the current declaration.  */
-static tree current_declspecs = NULL_TREE;
-static tree prefix_attributes = NULL_TREE;
+static GTY(()) tree 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;
+
+/* Stack of saved values of current_declspecs, prefix_attributes and
+   all_prefix_attributes.  */
+static GTY(()) tree declspec_stack;
+
+/* 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 {                                                                  \
+    declspec_stack = tree_cons (build_tree_list (prefix_attributes,     \
+                                                all_prefix_attributes), \
+                               current_declspecs,                       \
+                               declspec_stack);                         \
+  } while (0)
 
-/* Stack of saved values of current_declspecs and prefix_attributes.  */
-static tree declspec_stack;
+#define POP_DECLSPEC_STACK                                             \
+  do {                                                                 \
+    current_declspecs = TREE_VALUE (declspec_stack);                   \
+    prefix_attributes = TREE_PURPOSE (TREE_PURPOSE (declspec_stack));  \
+    all_prefix_attributes = TREE_VALUE (TREE_PURPOSE (declspec_stack));        \
+    declspec_stack = TREE_CHAIN (declspec_stack);                      \
+  } while (0)
 
 /* For __extension__, save/restore the warning flags which are
    controlled by __extension__.  */
-#define SAVE_WARN_FLAGS()      \
-       size_int (pedantic | (warn_pointer_arith << 1))
-#define RESTORE_WARN_FLAGS(tval) \
-  do {                                     \
-    int val = tree_low_cst (tval, 0);      \
-    pedantic = val & 1;                    \
-    warn_pointer_arith = (val >> 1) & 1;   \
+#define SAVE_EXT_FLAGS()                       \
+       size_int (pedantic                      \
+                 | (warn_pointer_arith << 1)   \
+                 | (warn_traditional << 2)     \
+                 | (flag_iso << 3))
+
+#define RESTORE_EXT_FLAGS(tval)                        \
+  do {                                         \
+    int val = tree_low_cst (tval, 0);          \
+    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 information */
+/* Objective-C specific parser/lexer information */
 
-tree objc_interface_context;
-tree objc_implementation_context;
-tree objc_method_context;
-tree objc_ivar_chain;
-tree objc_ivar_context;
-enum tree_code objc_inherit_code;
-int objc_receiver_context;
-int objc_public_flag;
+static enum tree_code objc_inherit_code;
+static int objc_pq_context = 0, objc_public_flag = 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
 end ifobjc
 
+ifc
+#define OBJC_NEED_RAW_IDENTIFIER(VAL)  /* nothing */
+end ifc
+
+static bool parsing_iso_function_signature;
+
 /* Tell yyparse how to print a token's value, if yydebug is set.  */
 
 #define YYPRINT(FILE,YYCHAR,YYLVAL) yyprint(FILE,YYCHAR,YYLVAL)
 
 static void yyprint      PARAMS ((FILE *, int, YYSTYPE));
 static void yyerror      PARAMS ((const char *));
+static int yylexname     PARAMS ((void));
+static int yylexstring   PARAMS ((void));
 static inline int _yylex  PARAMS ((void));
 static int  yylex        PARAMS ((void));
 static void init_reswords PARAMS ((void));
 
-/* Add GC roots for variables local to this file.  */
+  /* Initialisation routine for this file.  */
 void
 c_parse_init ()
 {
-  ggc_add_tree_root (&declspec_stack, 1);
-  ggc_add_tree_root (&current_declspecs, 1);
-  ggc_add_tree_root (&prefix_attributes, 1);
-ifobjc
-  ggc_add_tree_root (&objc_interface_context, 1);
-  ggc_add_tree_root (&objc_implementation_context, 1);
-  ggc_add_tree_root (&objc_method_context, 1);
-  ggc_add_tree_root (&objc_ivar_chain, 1);
-  ggc_add_tree_root (&objc_ivar_context, 1);
-end ifobjc
+  init_reswords ();
 }
 
 %}
@@ -297,7 +367,11 @@ program: /* empty */
                     get us back to the global binding level.  */
                  while (! global_bindings_p ())
                    poplevel (0, 0, 0);
-                 finish_file ();
+                 /* __FUNCTION__ is defined at file scope ("").  This
+                    call may not be necessary as my tests indicate it
+                    still works without it.  */
+                 finish_fname_decls ();
+                  finish_file ();
                }
        ;
 
@@ -311,6 +385,11 @@ extdefs:
        ;
 
 extdef:
+       extdef_1
+       { parsing_iso_function_signature = false; } /* Reset after any external definition.  */
+       ;
+
+extdef_1:
        fndef
        | datadef
 ifobjc
@@ -325,30 +404,22 @@ end ifobjc
                  else
                    error ("argument of `asm' is not a constant string"); }
        | extension extdef
-               { RESTORE_WARN_FLAGS ($1); }
+               { RESTORE_EXT_FLAGS ($1); }
        ;
 
 datadef:
          setspecs notype_initdecls ';'
                { if (pedantic)
                    error ("ISO C forbids data definition with no type or storage class");
-                 else if (!flag_traditional)
-                   warning ("data definition has no type or storage class"); 
-
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-        | declmods setspecs notype_initdecls ';'
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | typed_declspecs setspecs initdecls ';'
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-        | declmods ';'
-         { pedwarn ("empty declaration"); }
-       | typed_declspecs ';'
+                 else
+                   warning ("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 ($1); }
        | error ';'
        | error '}'
@@ -358,60 +429,48 @@ datadef:
        ;
 \f
 fndef:
-         typed_declspecs setspecs declarator
+         declspecs_ts setspecs declarator
                { if (! start_function (current_declspecs, $3,
-                                       prefix_attributes, NULL_TREE))
+                                       all_prefix_attributes))
                    YYERROR1;
                }
-         old_style_parm_decls
-               { store_parm_decls (); }
-         save_filename save_lineno compstmt_or_error
-               { DECL_SOURCE_FILE (current_function_decl) = $7;
-                 DECL_SOURCE_LINE (current_function_decl) = $8;
-                 finish_function (0); 
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | typed_declspecs setspecs declarator error
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | declmods setspecs notype_declarator
+         old_style_parm_decls  save_filename save_lineno
+               { DECL_SOURCE_FILE (current_function_decl) = $6;
+                 DECL_SOURCE_LINE (current_function_decl) = $7;
+                 store_parm_decls (); }
+        compstmt_or_error
+               { finish_function (0, 1);
+                 POP_DECLSPEC_STACK; }
+       | declspecs_ts setspecs declarator error
+               { POP_DECLSPEC_STACK; }
+       | declspecs_nots setspecs notype_declarator
                { if (! start_function (current_declspecs, $3,
-                                       prefix_attributes, NULL_TREE))
+                                       all_prefix_attributes))
                    YYERROR1;
                }
-         old_style_parm_decls
-               { store_parm_decls (); }
-         save_filename save_lineno compstmt_or_error
-               { DECL_SOURCE_FILE (current_function_decl) = $7;
-                 DECL_SOURCE_LINE (current_function_decl) = $8;
-                 finish_function (0); 
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | declmods setspecs notype_declarator error
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
+         old_style_parm_decls save_filename save_lineno
+               { DECL_SOURCE_FILE (current_function_decl) = $6;
+                 DECL_SOURCE_LINE (current_function_decl) = $7;
+                 store_parm_decls (); }
+         compstmt_or_error
+               { finish_function (0, 1);
+                 POP_DECLSPEC_STACK; }
+       | declspecs_nots setspecs notype_declarator error
+               { POP_DECLSPEC_STACK; }
        | setspecs notype_declarator
                { if (! start_function (NULL_TREE, $2,
-                                       prefix_attributes, NULL_TREE))
+                                       all_prefix_attributes))
                    YYERROR1;
                }
-         old_style_parm_decls
-               { store_parm_decls (); }
-         save_filename save_lineno compstmt_or_error
-               { DECL_SOURCE_FILE (current_function_decl) = $6;
-                 DECL_SOURCE_LINE (current_function_decl) = $7;
-                 finish_function (0); 
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
+         old_style_parm_decls save_filename save_lineno
+               { DECL_SOURCE_FILE (current_function_decl) = $5;
+                 DECL_SOURCE_LINE (current_function_decl) = $6;
+                 store_parm_decls (); }
+         compstmt_or_error
+               { finish_function (0, 1);
+                 POP_DECLSPEC_STACK; }
        | setspecs notype_declarator error
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
+               { POP_DECLSPEC_STACK; }
        ;
 
 identifier:
@@ -419,7 +478,7 @@ identifier:
        | TYPENAME
 ifobjc
        | OBJECTNAME
-        | CLASSNAME
+       | CLASSNAME
 end ifobjc
        ;
 
@@ -468,39 +527,13 @@ unary_expr:
        /* __extension__ turns off -pedantic for following primary.  */
        | extension cast_expr     %prec UNARY
                { $$ = $2;
-                 RESTORE_WARN_FLAGS ($1); }
+                 RESTORE_EXT_FLAGS ($1); }
        | unop cast_expr  %prec UNARY
                { $$ = build_unary_op ($1, $2, 0);
                  overflow_warning ($$); }
        /* Refer to the address of a label as a pointer.  */
        | ANDAND identifier
-               { tree label = lookup_label ($2);
-                 if (pedantic)
-                   pedwarn ("ISO C forbids `&&'");
-                 if (label == 0)
-                   $$ = null_pointer_node;
-                 else
-                   {
-                     TREE_USED (label) = 1;
-                     $$ = build1 (ADDR_EXPR, ptr_type_node, label);
-                     TREE_CONSTANT ($$) = 1;
-                   }
-               }
-/* This seems to be impossible on some machines, so let's turn it off.
-   You can use __builtin_next_arg to find the anonymous stack args.
-       | '&' ELLIPSIS
-               { tree types = TYPE_ARG_TYPES (TREE_TYPE (current_function_decl));
-                 $$ = error_mark_node;
-                 if (TREE_VALUE (tree_last (types)) == void_type_node)
-                   error ("`&...' used in function with fixed number of arguments");
-                 else
-                   {
-                     if (pedantic)
-                       pedwarn ("ISO C forbids `&...'");
-                     $$ = tree_last (DECL_ARGUMENTS (current_function_decl));
-                     $$ = build_unary_op (ADDR_EXPR, $$, 0);
-                   } }
-*/
+               { $$ = finish_label_address_expr ($2); }
        | sizeof unary_expr  %prec UNARY
                { skip_evaluation--;
                  if (TREE_CODE ($2) == COMPONENT_REF
@@ -530,47 +563,14 @@ alignof:
        ALIGNOF { skip_evaluation++; }
        ;
 
+typeof:
+       TYPEOF { skip_evaluation++; }
+       ;
+
 cast_expr:
        unary_expr
        | '(' typename ')' cast_expr  %prec UNARY
-               { tree type;
-                 int SAVED_warn_strict_prototypes = warn_strict_prototypes;
-                 /* This avoids warnings about unprototyped casts on
-                     integers.  E.g. "#define SIG_DFL (void(*)())0".  */
-                 if (TREE_CODE ($4) == INTEGER_CST)
-                   warn_strict_prototypes = 0;
-                 type = groktypename ($2);
-                 warn_strict_prototypes = SAVED_warn_strict_prototypes;
-                 $$ = build_c_cast (type, $4); }
-       | '(' typename ')' '{' 
-               { start_init (NULL_TREE, NULL, 0);
-                 $2 = groktypename ($2);
-                 really_start_incremental_init ($2); }
-         initlist_maybe_comma '}'  %prec UNARY
-               { const char *name;
-                 tree result = pop_init_level (0);
-                 tree type = $2;
-                 finish_init ();
-
-                 if (pedantic && ! flag_isoc99)
-                   pedwarn ("ISO C89 forbids constructor expressions");
-                 if (TYPE_NAME (type) != 0)
-                   {
-                     if (TREE_CODE (TYPE_NAME (type)) == IDENTIFIER_NODE)
-                       name = IDENTIFIER_POINTER (TYPE_NAME (type));
-                     else
-                       name = IDENTIFIER_POINTER (DECL_NAME (TYPE_NAME (type)));
-                   }
-                 else
-                   name = "";
-                 $$ = result;
-                 if (TREE_CODE (type) == ARRAY_TYPE && !COMPLETE_TYPE_P (type))
-                   {
-                     int failure = complete_array_type (type, $$, 1);
-                     if (failure)
-                       abort ();
-                   }
-               }
+               { $$ = c_cast_expr ($2, $4); }
        ;
 
 expr_no_commas:
@@ -600,19 +600,22 @@ expr_no_commas:
        | expr_no_commas '^' expr_no_commas
                { $$ = parser_build_binary_op ($2, $1, $3); }
        | expr_no_commas ANDAND
-               { $1 = truthvalue_conversion (default_conversion ($1));
+               { $1 = c_common_truthvalue_conversion
+                   (default_conversion ($1));
                  skip_evaluation += $1 == boolean_false_node; }
          expr_no_commas
                { skip_evaluation -= $1 == boolean_false_node;
                  $$ = parser_build_binary_op (TRUTH_ANDIF_EXPR, $1, $4); }
        | expr_no_commas OROR
-               { $1 = truthvalue_conversion (default_conversion ($1));
+               { $1 = c_common_truthvalue_conversion
+                   (default_conversion ($1));
                  skip_evaluation += $1 == boolean_true_node; }
          expr_no_commas
                { skip_evaluation -= $1 == boolean_true_node;
                  $$ = parser_build_binary_op (TRUTH_ORIF_EXPR, $1, $4); }
        | expr_no_commas '?'
-               { $1 = truthvalue_conversion (default_conversion ($1));
+               { $1 = c_common_truthvalue_conversion
+                   (default_conversion ($1));
                  skip_evaluation += $1 == boolean_false_node; }
           expr ':'
                { skip_evaluation += (($1 == boolean_true_node)
@@ -625,7 +628,8 @@ expr_no_commas:
                    pedwarn ("ISO C forbids omitting the middle term of a ?: expression");
                  /* Make sure first operand is calculated only once.  */
                  $<ttype>2 = save_expr ($1);
-                 $1 = truthvalue_conversion (default_conversion ($<ttype>2));
+                 $1 = c_common_truthvalue_conversion
+                   (default_conversion ($<ttype>2));
                  skip_evaluation += $1 == boolean_true_node; }
          ':' expr_no_commas
                { skip_evaluation -= $1 == boolean_true_node;
@@ -634,17 +638,16 @@ expr_no_commas:
                { char class;
                  $$ = build_modify_expr ($1, NOP_EXPR, $3);
                  class = TREE_CODE_CLASS (TREE_CODE ($$));
-                 if (class == 'e' || class == '1'
-                     || class == '2' || class == '<')
+                 if (IS_EXPR_CODE_CLASS (class))
                    C_SET_EXP_ORIGINAL_CODE ($$, MODIFY_EXPR);
                }
        | expr_no_commas ASSIGN expr_no_commas
                { char class;
                  $$ = build_modify_expr ($1, $2, $3);
-                 /* This inhibits warnings in truthvalue_conversion.  */
+                 /* This inhibits warnings in
+                    c_common_truthvalue_conversion.  */
                  class = TREE_CODE_CLASS (TREE_CODE ($$));
-                 if (class == 'e' || class == '1'
-                     || class == '2' || class == '<')
+                 if (IS_EXPR_CODE_CLASS (class))
                    C_SET_EXP_ORIGINAL_CODE ($$, ERROR_MARK);
                }
        ;
@@ -657,12 +660,26 @@ primary:
                  $$ = build_external_ref ($1, yychar == '(');
                }
        | CONSTANT
-       | string
-               { $$ = combine_strings ($1); }
+       | STRING
+               { $$ = fix_string_type ($$); }
+       | VAR_FUNC_NAME
+               { $$ = fname_decl (C_RID_CODE ($$), $$); }
+       | '(' typename ')' '{'
+               { start_init (NULL_TREE, NULL, 0);
+                 $2 = groktypename ($2);
+                 really_start_incremental_init ($2); }
+         initlist_maybe_comma '}'  %prec UNARY
+               { tree constructor = pop_init_level (0);
+                 tree type = $2;
+                 finish_init ();
+
+                 if (pedantic && ! flag_isoc99)
+                   pedwarn ("ISO C89 forbids compound literals");
+                 $$ = build_compound_literal (type, constructor);
+               }
        | '(' expr ')'
                { char class = TREE_CODE_CLASS (TREE_CODE ($2));
-                 if (class == 'e' || class == '1'
-                     || class == '2' || class == '<')
+                 if (IS_EXPR_CODE_CLASS (class))
                    C_SET_EXP_ORIGINAL_CODE ($2, ERROR_MARK);
                  $$ = $2; }
        | '(' error ')'
@@ -694,37 +711,48 @@ primary:
                { $$ = build_function_call ($1, $3); }
        | VA_ARG '(' expr_no_commas ',' typename ')'
                { $$ = build_va_arg ($3, groktypename ($5)); }
+
+      | CHOOSE_EXPR '(' expr_no_commas ',' expr_no_commas ',' expr_no_commas ')'
+               {
+                  tree c;
+
+                  c = fold ($3);
+                  STRIP_NOPS (c);
+                  if (TREE_CODE (c) != INTEGER_CST)
+                    error ("first argument to __builtin_choose_expr not a constant");
+                  $$ = integer_zerop (c) ? $7 : $5;
+               }
+      | TYPES_COMPATIBLE_P '(' typename ',' typename ')'
+               {
+                 tree e1, e2;
+
+                 e1 = TYPE_MAIN_VARIANT (groktypename ($3));
+                 e2 = TYPE_MAIN_VARIANT (groktypename ($5));
+
+                 $$ = comptypes (e1, e2)
+                   ? build_int_2 (1, 0) : build_int_2 (0, 0);
+               }
        | primary '[' expr ']'   %prec '.'
                { $$ = build_array_ref ($1, $3); }
        | primary '.' identifier
                {
 ifobjc
-                  if (doing_objc_thang)
-                    {
-                     if (is_public ($1, $3))
-                       $$ = build_component_ref ($1, $3);
-                     else
-                       $$ = error_mark_node;
-                   }
-                  else
+                   if (!is_public ($1, $3))
+                     $$ = error_mark_node;
+                   else
 end ifobjc
-                   $$ = build_component_ref ($1, $3);
+                     $$ = build_component_ref ($1, $3);
                }
        | primary POINTSAT identifier
                {
                   tree expr = build_indirect_ref ($1, "->");
 
 ifobjc
-                  if (doing_objc_thang)
-                    {
-                     if (is_public (expr, $3))
-                       $$ = build_component_ref (expr, $3);
-                     else
+                     if (!is_public (expr, $3))
                        $$ = error_mark_node;
-                   }
-                  else
+                     else
 end ifobjc
-                    $$ = build_component_ref (expr, $3);
+                       $$ = build_component_ref (expr, $3);
                }
        | primary PLUSPLUS
                { $$ = build_unary_op (POSTINCREMENT_EXPR, $1, 0); }
@@ -744,47 +772,33 @@ ifobjc
 end ifobjc
        ;
 
-/* Produces a STRING_CST with perhaps more STRING_CSTs chained onto it.  */
-string:
-         STRING
-       | string STRING
-               {
-ifc
-                  static int last_lineno = 0;
-                  static const char *last_input_filename = 0;
-end ifc
-                  $$ = chainon ($1, $2);
-ifc
-                 if (warn_traditional && !in_system_header
-                     && (lineno != last_lineno || !last_input_filename ||
-                         strcmp (last_input_filename, input_filename)))
-                   {
-                     warning ("traditional C rejects string concatenation");
-                     last_lineno = lineno;
-                     last_input_filename = input_filename;
-                   }
-end ifc
-               }
-       ;
-
 ifobjc
 /* Produces an STRING_CST with perhaps more STRING_CSTs chained
    onto it, which is to be read as an ObjC string object.  */
 objc_string:
-         OBJC_STRING
-       | objc_string OBJC_STRING
-               { $$ = chainon ($1, $2); }
+         '@' STRING
+               { $$ = $2; }
+       | objc_string '@' STRING
+               { $$ = chainon ($1, $3); }
        ;
 end ifobjc
 
 old_style_parm_decls:
+       old_style_parm_decls_1
+       {
+         parsing_iso_function_signature = false; /* Reset after decls.  */
+       }
+       ;
+
+old_style_parm_decls_1:
        /* empty */
+       {
+         if (warn_traditional && !in_system_header
+             && parsing_iso_function_signature)
+           warning ("traditional C rejects ISO C style function definitions");
+         parsing_iso_function_signature = false; /* Reset after warning.  */
+       }
        | datadecls
-       | datadecls ELLIPSIS
-               /* ... is used here to indicate a varargs function.  */
-               { c_mark_varargs ();
-                 if (pedantic)
-                   pedwarn ("ISO C does not permit use of `varargs.h'"); }
        ;
 
 /* The following are analogous to lineno_decl, decls and decl
@@ -807,18 +821,14 @@ datadecls:
    attribute suffix, or function defn with attribute prefix on first old
    style parm.  */
 datadecl:
-       typed_declspecs_no_prefix_attr setspecs initdecls ';'
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | declmods_no_prefix_attr setspecs notype_initdecls ';'
-               { current_declspecs = TREE_VALUE (declspec_stack);      
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | typed_declspecs_no_prefix_attr ';'
+       declspecs_ts_nosa setspecs initdecls ';'
+               { POP_DECLSPEC_STACK; }
+       | declspecs_nots_nosa setspecs notype_initdecls ';'
+               { POP_DECLSPEC_STACK; }
+       | declspecs_ts_nosa ';'
                { shadow_tag_warned ($1, 1);
                  pedwarn ("empty declaration"); }
-       | declmods_no_prefix_attr ';'
+       | declspecs_nots_nosa ';'
                { pedwarn ("empty declaration"); }
        ;
 
@@ -837,113 +847,325 @@ lineno_decl:
    for the sake of parm declarations nested in function declarators.  */
 setspecs: /* empty */
                { pending_xref_error ();
-                 declspec_stack = tree_cons (prefix_attributes,
-                                             current_declspecs,
-                                             declspec_stack);
+                 PUSH_DECLSPEC_STACK;
                  split_specs_attrs ($<ttype>0,
-                                    &current_declspecs, &prefix_attributes); }
+                                    &current_declspecs, &prefix_attributes);
+                 all_prefix_attributes = prefix_attributes; }
        ;
 
-/* ??? Yuck.  See after_type_declarator.  */
-setattrs: /* empty */
-               { prefix_attributes = chainon (prefix_attributes, $<ttype>0); }
+/* 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:
-       typed_declspecs setspecs initdecls ';'
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | declmods setspecs notype_initdecls ';'
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | typed_declspecs setspecs nested_function
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | declmods setspecs notype_nested_function
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | typed_declspecs ';'
+       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 ($1); }
-       | declmods ';'
-               { pedwarn ("empty declaration"); }
        | extension decl
-               { RESTORE_WARN_FLAGS ($1); }
+               { 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).
+
+   These are stored as a TREE_LIST; the head of the list is the last
+   item in the specifier list.  Each entry in the list has either a
+   TREE_PURPOSE that is an attribute specifier list, or a TREE_VALUE that
+   is a single other specifier or qualifier; and a TREE_CHAIN that is the
+   rest of the list.  TREE_STATIC is set on the list if something other
+   than a storage class specifier or attribute has been seen; this is used
+   to warn for the obsolescent usage of storage class specifiers other than
+   at the start of the list.  (Doing this properly would require function
+   specifiers to be handled separately from storage class specifiers.)
+
+   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 have a non-NULL TREE_VALUE, attributes do not.  */
 
-typed_declspecs:
-         typespec reserved_declspecs
-               { $$ = tree_cons (NULL_TREE, $1, $2); }
-       | declmods typespec reserved_declspecs
-               { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
+declspecs_nosc_nots_nosa_noea:
+         TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_nosa_noea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_nosa_ea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
        ;
 
-reserved_declspecs:  /* empty */
-               { $$ = NULL_TREE; }
-       | reserved_declspecs typespecqual_reserved
-               { $$ = tree_cons (NULL_TREE, $2, $1); }
-       | reserved_declspecs SCSPEC
-               { if (extra_warnings)
+declspecs_nosc_nots_nosa_ea:
+         declspecs_nosc_nots_nosa_noea attributes
+               { $$ = tree_cons ($2, NULL_TREE, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       ;
+
+declspecs_nosc_nots_sa_noea:
+         declspecs_nosc_nots_sa_noea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_sa_ea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       ;
+
+declspecs_nosc_nots_sa_ea:
+         attributes
+               { $$ = tree_cons ($1, NULL_TREE, NULL_TREE);
+                 TREE_STATIC ($$) = 0; }
+       | declspecs_nosc_nots_sa_noea attributes
+               { $$ = tree_cons ($2, NULL_TREE, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       ;
+
+declspecs_nosc_ts_nosa_noea:
+         typespec_nonattr
+               { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_nosa_noea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_nosa_ea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_nosa_noea typespec_reserved_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_nosa_ea typespec_reserved_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_nosa_noea typespec_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_nosa_ea typespec_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       ;
+
+declspecs_nosc_ts_nosa_ea:
+         typespec_attr
+               { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_nosa_noea attributes
+               { $$ = tree_cons ($2, NULL_TREE, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_nosc_ts_nosa_noea typespec_reserved_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_nosa_ea typespec_reserved_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_nosa_noea typespec_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_nosa_ea typespec_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       ;
+
+declspecs_nosc_ts_sa_noea:
+         declspecs_nosc_ts_sa_noea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_sa_ea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_sa_noea typespec_reserved_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_sa_ea typespec_reserved_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_sa_noea typespec_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_sa_ea typespec_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       ;
+
+declspecs_nosc_ts_sa_ea:
+         declspecs_nosc_ts_sa_noea attributes
+               { $$ = tree_cons ($2, NULL_TREE, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_nosc_ts_sa_noea typespec_reserved_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_sa_ea typespec_reserved_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_sa_noea typespec_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_sa_ea typespec_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       ;
+
+declspecs_sc_nots_nosa_noea:
+         scspec
+               { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
+                 TREE_STATIC ($$) = 0; }
+       | declspecs_sc_nots_nosa_noea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_nosa_ea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_nosa_noea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_nosc_nots_nosa_ea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_nots_nosa_noea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
                    warning ("`%s' is not at beginning of declaration",
                             IDENTIFIER_POINTER ($2));
-                 $$ = tree_cons (NULL_TREE, $2, $1); }
-       | reserved_declspecs attributes
-               { $$ = tree_cons ($2, NULL_TREE, $1); }
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_nots_nosa_ea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
        ;
 
-typed_declspecs_no_prefix_attr:
-         typespec reserved_declspecs_no_prefix_attr
-               { $$ = tree_cons (NULL_TREE, $1, $2); }
-       | declmods_no_prefix_attr typespec reserved_declspecs_no_prefix_attr
-               { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
+declspecs_sc_nots_nosa_ea:
+         declspecs_sc_nots_nosa_noea attributes
+               { $$ = tree_cons ($2, NULL_TREE, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
        ;
 
-reserved_declspecs_no_prefix_attr:
-         /* empty */
-               { $$ = NULL_TREE; }
-       | reserved_declspecs_no_prefix_attr typespecqual_reserved
-               { $$ = tree_cons (NULL_TREE, $2, $1); }
-       | reserved_declspecs_no_prefix_attr SCSPEC
-               { if (extra_warnings)
+declspecs_sc_nots_sa_noea:
+         declspecs_sc_nots_sa_noea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_sa_ea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_nots_sa_noea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_nosc_nots_sa_ea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
                    warning ("`%s' is not at beginning of declaration",
                             IDENTIFIER_POINTER ($2));
-                 $$ = tree_cons (NULL_TREE, $2, $1); }
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_nots_sa_noea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_nots_sa_ea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
        ;
 
-/* List of just storage classes, type modifiers, and prefix attributes.
-   A declaration can start with just this, but then it cannot be used
-   to redeclare a typedef-name.
-   Declspecs have a non-NULL TREE_VALUE, attributes do not.  */
-
-declmods:
-         declmods_no_prefix_attr
-               { $$ = $1; }
-       | attributes
-               { $$ = tree_cons ($1, NULL_TREE, NULL_TREE); }
-       | declmods declmods_no_prefix_attr
-               { $$ = chainon ($2, $1); }
-       | declmods attributes
-               { $$ = tree_cons ($2, NULL_TREE, $1); }
+declspecs_sc_nots_sa_ea:
+         declspecs_sc_nots_sa_noea attributes
+               { $$ = tree_cons ($2, NULL_TREE, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
        ;
 
-declmods_no_prefix_attr:
-         TYPE_QUAL
-               { $$ = tree_cons (NULL_TREE, $1, NULL_TREE);
+declspecs_sc_ts_nosa_noea:
+         declspecs_sc_ts_nosa_noea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
                  TREE_STATIC ($$) = 1; }
-       | SCSPEC
-               { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
-       | declmods_no_prefix_attr TYPE_QUAL
+       | declspecs_sc_ts_nosa_ea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_ts_nosa_noea typespec_reserved_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_ts_nosa_ea typespec_reserved_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_nosa_noea typespec_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_nosa_ea typespec_nonattr
                { $$ = tree_cons (NULL_TREE, $2, $1);
                  TREE_STATIC ($$) = 1; }
-       | declmods_no_prefix_attr SCSPEC
+       | declspecs_nosc_ts_nosa_noea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_nosc_ts_nosa_ea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_ts_nosa_noea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_ts_nosa_ea scspec
                { if (extra_warnings && TREE_STATIC ($1))
                    warning ("`%s' is not at beginning of declaration",
                             IDENTIFIER_POINTER ($2));
@@ -951,31 +1173,218 @@ declmods_no_prefix_attr:
                  TREE_STATIC ($$) = TREE_STATIC ($1); }
        ;
 
+declspecs_sc_ts_nosa_ea:
+         declspecs_sc_ts_nosa_noea attributes
+               { $$ = tree_cons ($2, NULL_TREE, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_ts_nosa_noea typespec_reserved_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_ts_nosa_ea typespec_reserved_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_nosa_noea typespec_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_nosa_ea typespec_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       ;
 
-/* Used instead of declspecs where storage classes are not allowed
-   (that is, for typenames and structure components).
-   Don't accept a typedef-name if anything but a modifier precedes it.  */
+declspecs_sc_ts_sa_noea:
+         declspecs_sc_ts_sa_noea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_ts_sa_ea TYPE_QUAL
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_ts_sa_noea typespec_reserved_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_ts_sa_ea typespec_reserved_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_sa_noea typespec_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_sa_ea typespec_nonattr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_nosc_ts_sa_noea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_nosc_ts_sa_ea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_ts_sa_noea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_ts_sa_ea scspec
+               { if (extra_warnings && TREE_STATIC ($1))
+                   warning ("`%s' is not at beginning of declaration",
+                            IDENTIFIER_POINTER ($2));
+                 $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       ;
 
-typed_typespecs:
-         typespec reserved_typespecquals
-               { $$ = tree_cons (NULL_TREE, $1, $2); }
-       | nonempty_type_quals typespec reserved_typespecquals
-               { $$ = chainon ($3, tree_cons (NULL_TREE, $2, $1)); }
+declspecs_sc_ts_sa_ea:
+         declspecs_sc_ts_sa_noea attributes
+               { $$ = tree_cons ($2, NULL_TREE, $1);
+                 TREE_STATIC ($$) = TREE_STATIC ($1); }
+       | declspecs_sc_ts_sa_noea typespec_reserved_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_ts_sa_ea typespec_reserved_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_sa_noea typespec_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
+       | declspecs_sc_nots_sa_ea typespec_attr
+               { $$ = tree_cons (NULL_TREE, $2, $1);
+                 TREE_STATIC ($$) = 1; }
        ;
 
-reserved_typespecquals:  /* empty */
+/* 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_TREE; }
-       | reserved_typespecquals typespecqual_reserved
-               { $$ = tree_cons (NULL_TREE, $2, $1); }
+       | declspecs_nosc_nots
+               { $$ = $1; }
        ;
 
-/* A typespec (but not a type qualifier).
+/* 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.  */
+   if a typedef name appears then it is being redeclared.
 
-typespec: TYPESPEC
-       | structsp
-       | TYPENAME
+   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: specifiers.  */
+
+typespec_nonattr:
+         typespec_reserved_nonattr
+       | typespec_nonreserved_nonattr
+       ;
+
+typespec_attr:
+         typespec_reserved_attr
+       ;
+
+typespec_reserved_nonattr:
+         TYPESPEC
+               { OBJC_NEED_RAW_IDENTIFIER (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;'.  */
                  $$ = lookup_name ($1); }
@@ -990,42 +1399,35 @@ ifobjc
         | non_empty_protocolrefs
                 { $$ = get_object_reference ($1); }
 end ifobjc
-       | TYPEOF '(' expr ')'
-               { $$ = TREE_TYPE ($3); }
-       | TYPEOF '(' typename ')'
-               { $$ = groktypename ($3); }
+       | typeof '(' expr ')'
+               { skip_evaluation--; $$ = TREE_TYPE ($3); }
+       | typeof '(' typename ')'
+               { skip_evaluation--; $$ = groktypename ($3); }
        ;
 
-/* A typespec that is a reserved word, or a type qualifier.  */
-
-typespecqual_reserved: TYPESPEC
-       | TYPE_QUAL
-       | structsp
-       ;
+/* typespec_nonreserved_attr does not exist.  */
 
 initdecls:
        initdcl
-       | initdecls ',' initdcl
+       | initdecls ',' maybe_resetattrs initdcl
        ;
 
 notype_initdecls:
        notype_initdcl
-       | notype_initdecls ',' initdcl
+       | notype_initdecls ',' maybe_resetattrs notype_initdcl
        ;
 
 maybeasm:
          /* empty */
                { $$ = NULL_TREE; }
-       | ASM_KEYWORD '(' string ')'
-               { if (TREE_CHAIN ($3)) $3 = combine_strings ($3);
-                 $$ = $3;
-               }
+       | ASM_KEYWORD '(' STRING ')'
+               { $$ = $3; }
        ;
 
 initdcl:
          declarator maybeasm maybe_attribute '='
                { $<ttype>$ = start_decl ($1, current_declspecs, 1,
-                                         $3, prefix_attributes);
+                                         chainon ($3, all_prefix_attributes));
                  start_init ($<ttype>$, $2, global_bindings_p ()); }
          init
 /* Note how the declaration of the variable is in effect while its init is parsed! */
@@ -1033,35 +1435,34 @@ initdcl:
                  finish_decl ($<ttype>5, $6, $2); }
        | declarator maybeasm maybe_attribute
                { tree d = start_decl ($1, current_declspecs, 0,
-                                      $3, prefix_attributes);
-                 finish_decl (d, NULL_TREE, $2); 
+                                      chainon ($3, all_prefix_attributes));
+                 finish_decl (d, NULL_TREE, $2);
                 }
        ;
 
 notype_initdcl:
          notype_declarator maybeasm maybe_attribute '='
                { $<ttype>$ = start_decl ($1, current_declspecs, 1,
-                                         $3, prefix_attributes);
+                                         chainon ($3, all_prefix_attributes));
                  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 ();
-                 decl_attributes ($<ttype>5, $3, prefix_attributes);
                  finish_decl ($<ttype>5, $6, $2); }
        | notype_declarator maybeasm maybe_attribute
                { tree d = start_decl ($1, current_declspecs, 0,
-                                      $3, prefix_attributes);
+                                      chainon ($3, all_prefix_attributes));
                  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; }
+               { $$ = NULL_TREE; }
        | attributes
                { $$ = $1; }
        ;
+
 attributes:
       attribute
                { $$ = $1; }
@@ -1080,7 +1481,7 @@ attribute_list:
        | attribute_list ',' attrib
                { $$ = chainon ($1, $3); }
        ;
+
 attrib:
     /* empty */
                { $$ = NULL_TREE; }
@@ -1099,10 +1500,15 @@ attrib:
 
 any_word:
          identifier
-       | SCSPEC
+       | scspec
        | TYPESPEC
        | TYPE_QUAL
        ;
+
+scspec:
+         STATIC
+       | SCSPEC
+       ;
 \f
 /* Initializers.  `init' is the entry point.  */
 
@@ -1143,6 +1549,7 @@ initelt:
                  if (pedantic)
                    pedwarn ("obsolete use of designated initializer with `:'"); }
          initval
+               {}
        | initval
        ;
 
@@ -1164,17 +1571,12 @@ designator_list:
 designator:
          '.' identifier
                { set_init_label ($2); }
-       /* These are for labeled elements.  The syntax for an array element
-          initializer conflicts with the syntax for an Objective-C message,
-          so don't include these productions in the Objective-C grammar.  */
-ifc
        | '[' expr_no_commas ELLIPSIS expr_no_commas ']'
                { set_init_index ($2, $4);
                  if (pedantic)
                    pedwarn ("ISO C forbids specifying range of elements to initialize"); }
        | '[' expr_no_commas ']'
                { set_init_index ($2, NULL_TREE); }
-end ifc
        ;
 \f
 nested_function:
@@ -1184,26 +1586,28 @@ nested_function:
 
                  push_function_context ();
                  if (! start_function (current_declspecs, $1,
-                                       prefix_attributes, NULL_TREE))
+                                       all_prefix_attributes))
                    {
                      pop_function_context ();
                      YYERROR1;
                    }
+                 parsing_iso_function_signature = false; /* Don't warn about nested functions.  */
                }
-          old_style_parm_decls
-               { store_parm_decls (); }
+          old_style_parm_decls save_filename save_lineno
+               { tree decl = current_function_decl;
+                 DECL_SOURCE_FILE (decl) = $4;
+                 DECL_SOURCE_LINE (decl) = $5;
+                 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.  */
-         save_filename save_lineno compstmt
+         compstmt
                { tree decl = current_function_decl;
-                 DECL_SOURCE_FILE (decl) = $5;
-                 DECL_SOURCE_LINE (decl) = $6;
-                 finish_function (1);
-                 pop_function_context (); 
+                 finish_function (1, 1);
+                 pop_function_context ();
                  add_decl_stmt (decl); }
        ;
 
@@ -1214,26 +1618,28 @@ notype_nested_function:
 
                  push_function_context ();
                  if (! start_function (current_declspecs, $1,
-                                       prefix_attributes, NULL_TREE))
+                                       all_prefix_attributes))
                    {
                      pop_function_context ();
                      YYERROR1;
                    }
+                 parsing_iso_function_signature = false; /* Don't warn about nested functions.  */
                }
-         old_style_parm_decls
-               { store_parm_decls (); }
+         old_style_parm_decls save_filename save_lineno
+               { tree decl = current_function_decl;
+                 DECL_SOURCE_FILE (decl) = $4;
+                 DECL_SOURCE_LINE (decl) = $5;
+                 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.  */
-         save_filename save_lineno compstmt
+         compstmt
                { tree decl = current_function_decl;
-                 DECL_SOURCE_FILE (decl) = $5;
-                 DECL_SOURCE_LINE (decl) = $6;
-                 finish_function (1);
-                 pop_function_context (); 
+                 finish_function (1, 1);
+                 pop_function_context ();
                  add_decl_stmt (decl); }
        ;
 
@@ -1248,26 +1654,17 @@ declarator:
 /* A declarator that is allowed only after an explicit typespec.  */
 
 after_type_declarator:
-         '(' after_type_declarator ')'
-               { $$ = $2; }
+         '(' maybe_attribute after_type_declarator ')'
+               { $$ = $2 ? tree_cons ($2, $3, NULL_TREE) : $3; }
        | after_type_declarator '(' parmlist_or_identifiers  %prec '.'
                { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
 /*     | after_type_declarator '(' error ')'  %prec '.'
                { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
                  poplevel (0, 0, 0); }  */
-       | after_type_declarator '[' expr ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, $3); }
-       | after_type_declarator '[' ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
-       | '*' type_quals after_type_declarator  %prec UNARY
+       | after_type_declarator array_declarator  %prec '.'
+               { $$ = set_array_declarator_type ($2, $1, 0); }
+       | '*' maybe_type_quals_attrs after_type_declarator  %prec UNARY
                { $$ = make_pointer_declarator ($2, $3); }
-       /* ??? Yuck.  setattrs is a quick hack.  We can't use
-          prefix_attributes because $1 only applies to this
-          declarator.  We assume setspecs has already been done.
-          setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
-          attributes could be recognized here or in `attributes').  */
-       | attributes setattrs after_type_declarator
-               { $$ = $3; }
        | TYPENAME
 ifobjc
        | OBJECTNAME
@@ -1278,34 +1675,39 @@ end ifobjc
    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 '(' parmlist_or_identifiers  %prec '.'
+         parm_declarator_starttypename
+       | parm_declarator_nostarttypename
+       ;
+
+parm_declarator_starttypename:
+         parm_declarator_starttypename '(' parmlist_or_identifiers  %prec '.'
                { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
-/*     | parm_declarator '(' error ')'  %prec '.'
+/*     | parm_declarator_starttypename '(' error ')'  %prec '.'
                { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
                  poplevel (0, 0, 0); }  */
-ifc
-       | parm_declarator '[' '*' ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
-                 if (! flag_isoc99)
-                   error ("`[*]' in parameter declaration only allowed in ISO C 99");
-               }
-end ifc
-       | parm_declarator '[' expr ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, $3); }
-       | parm_declarator '[' ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
-       | '*' type_quals parm_declarator  %prec UNARY
-               { $$ = make_pointer_declarator ($2, $3); }
-       /* ??? Yuck.  setattrs is a quick hack.  We can't use
-          prefix_attributes because $1 only applies to this
-          declarator.  We assume setspecs has already been done.
-          setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
-          attributes could be recognized here or in `attributes').  */
-       | attributes setattrs parm_declarator
-               { $$ = $3; }
+       | parm_declarator_starttypename array_declarator  %prec '.'
+               { $$ = set_array_declarator_type ($2, $1, 0); }
        | TYPENAME
+ifobjc
+       | OBJECTNAME
+end ifobjc
+       ;
+
+parm_declarator_nostarttypename:
+         parm_declarator_nostarttypename '(' parmlist_or_identifiers  %prec '.'
+               { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
+/*     | parm_declarator_nostarttypename '(' error ')'  %prec '.'
+               { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
+                 poplevel (0, 0, 0); }  */
+       | parm_declarator_nostarttypename array_declarator  %prec '.'
+               { $$ = set_array_declarator_type ($2, $1, 0); }
+       | '*' 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 ? tree_cons ($2, $3, NULL_TREE) : $3; }
        ;
 
 /* A declarator allowed whether or not there has been
@@ -1317,28 +1719,12 @@ notype_declarator:
 /*     | notype_declarator '(' error ')'  %prec '.'
                { $$ = build_nt (CALL_EXPR, $1, NULL_TREE, NULL_TREE);
                  poplevel (0, 0, 0); }  */
-       | '(' notype_declarator ')'
-               { $$ = $2; }
-       | '*' type_quals notype_declarator  %prec UNARY
+       | '(' maybe_attribute notype_declarator ')'
+               { $$ = $2 ? tree_cons ($2, $3, NULL_TREE) : $3; }
+       | '*' maybe_type_quals_attrs notype_declarator  %prec UNARY
                { $$ = make_pointer_declarator ($2, $3); }
-ifc
-       | notype_declarator '[' '*' ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, NULL_TREE);
-                 if (! flag_isoc99)
-                   error ("`[*]' in parameter declaration only allowed in ISO C 99");
-               }
-end ifc
-       | notype_declarator '[' expr ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, $3); }
-       | notype_declarator '[' ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
-       /* ??? Yuck.  setattrs is a quick hack.  We can't use
-          prefix_attributes because $1 only applies to this
-          declarator.  We assume setspecs has already been done.
-          setattrs also avoids 5 reduce/reduce conflicts (otherwise multiple
-          attributes could be recognized here or in `attributes').  */
-       | attributes setattrs notype_declarator
-               { $$ = $3; }
+       | notype_declarator array_declarator  %prec '.'
+               { $$ = set_array_declarator_type ($2, $1, 0); }
        | IDENTIFIER
        ;
 
@@ -1363,29 +1749,33 @@ enum_head:
                { $$ = $2; }
        ;
 
-structsp:
+/* 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 '{'
                { $$ = start_struct (RECORD_TYPE, $2);
                  /* Start scope of tag before parsing components.  */
                }
-         component_decl_list '}' maybe_attribute 
-               { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
+         component_decl_list '}' maybe_attribute
+               { $$ = finish_struct ($<ttype>4, nreverse ($5),
+                                     chainon ($1, $7)); }
        | struct_head '{' component_decl_list '}' maybe_attribute
                { $$ = finish_struct (start_struct (RECORD_TYPE, NULL_TREE),
-                                     $3, chainon ($1, $5));
+                                     nreverse ($3), chainon ($1, $5));
                }
-       | struct_head identifier
-               { $$ = xref_tag (RECORD_TYPE, $2); }
        | union_head identifier '{'
                { $$ = start_struct (UNION_TYPE, $2); }
          component_decl_list '}' maybe_attribute
-               { $$ = finish_struct ($<ttype>4, $5, chainon ($1, $7)); }
+               { $$ = finish_struct ($<ttype>4, nreverse ($5),
+                                     chainon ($1, $7)); }
        | union_head '{' component_decl_list '}' maybe_attribute
                { $$ = finish_struct (start_struct (UNION_TYPE, NULL_TREE),
-                                     $3, chainon ($1, $5));
+                                     nreverse ($3), chainon ($1, $5));
                }
-       | union_head identifier
-               { $$ = xref_tag (UNION_TYPE, $2); }
        | enum_head identifier '{'
                { $$ = start_enum ($2); }
          enumlist maybecomma_warn '}' maybe_attribute
@@ -1396,8 +1786,19 @@ structsp:
          enumlist maybecomma_warn '}' maybe_attribute
                { $$ = finish_enum ($<ttype>3, nreverse ($4),
                                    chainon ($1, $7)); }
+       ;
+
+structsp_nonattr:
+         struct_head identifier
+               { $$ = xref_tag (RECORD_TYPE, $2); }
+       | union_head identifier
+               { $$ = xref_tag (UNION_TYPE, $2); }
        | enum_head identifier
-               { $$ = xref_tag (ENUMERAL_TYPE, $2); }
+               { $$ = xref_tag (ENUMERAL_TYPE, $2);
+                 /* In ISO C, enumerated types can be referred to
+                    only if already defined.  */
+                 if (pedantic && !COMPLETE_TYPE_P ($$))
+                   pedwarn ("ISO C forbids forward references to `enum' types"); }
        ;
 
 maybecomma:
@@ -1412,18 +1813,30 @@ maybecomma_warn:
                    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 ($1, $2);
+               { $$ = chainon ($2, $1);
                  pedwarn ("no semicolon at end of struct or union"); }
        ;
 
 component_decl_list2:  /* empty */
                { $$ = NULL_TREE; }
        | component_decl_list2 component_decl ';'
-               { $$ = chainon ($1, $2); }
+               { $$ = chainon ($2, $1); }
        | component_decl_list2 ';'
                { if (pedantic)
                    pedwarn ("extra semicolon in struct or union specified"); }
@@ -1434,10 +1847,10 @@ ifobjc
                  tree interface = lookup_interface ($3);
 
                  if (interface)
-                   $$ = get_class_ivars (interface);
+                   $$ = nreverse (get_class_ivars (interface));
                  else
                    {
-                     error ("Cannot find interface declaration for `%s'",
+                     error ("cannot find interface declaration for `%s'",
                             IDENTIFIER_POINTER ($3));
                      $$ = NULL_TREE;
                    }
@@ -1445,40 +1858,24 @@ ifobjc
 end ifobjc
        ;
 
-/* There is a shift-reduce conflict here, because `components' may
-   start with a `typename'.  It happens that shifting (the default resolution)
-   does the right thing, because it treats the `typename' as part of
-   a `typed_typespecs'.
-
-   It is possible that this same technique would allow the distinction
-   between `notype_initdecls' and `initdecls' to be eliminated.
-   But I am being cautious and not trying it.  */
-
 component_decl:
-         typed_typespecs setspecs components
+         declspecs_nosc_ts setspecs components
                { $$ = $3;
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | typed_typespecs setspecs save_filename save_lineno maybe_attribute
+                 POP_DECLSPEC_STACK; }
+       | declspecs_nosc_ts setspecs save_filename save_lineno
                {
-                 /* Support for unnamed structs or unions as members of 
-                    structs or unions (which is [a] useful and [b] supports 
+                 /* Support for unnamed structs or unions as members of
+                    structs or unions (which is [a] useful and [b] supports
                     MS P-SDK).  */
                  if (pedantic)
                    pedwarn ("ISO C doesn't support unnamed structs/unions");
 
                  $$ = grokfield($3, $4, NULL, current_declspecs, NULL_TREE);
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack);
-               }
-    | nonempty_type_quals setspecs components
+                 POP_DECLSPEC_STACK; }
+       | declspecs_nosc_nots setspecs components_notype
                { $$ = $3;
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | nonempty_type_quals
+                 POP_DECLSPEC_STACK; }
+       | declspecs_nosc_nots
                { if (pedantic)
                    pedwarn ("ISO C forbids member declarations with no members");
                  shadow_tag($1);
@@ -1487,32 +1884,49 @@ component_decl:
                { $$ = NULL_TREE; }
        | extension component_decl
                { $$ = $2;
-                 RESTORE_WARN_FLAGS ($1); }
+                 RESTORE_EXT_FLAGS ($1); }
        ;
 
 components:
          component_declarator
-       | components ',' component_declarator
-               { $$ = chainon ($1, $3); }
+       | 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:
          save_filename save_lineno declarator maybe_attribute
                { $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
-                 decl_attributes ($$, $4, prefix_attributes); }
+                 decl_attributes (&$$, chainon ($4, all_prefix_attributes), 0); }
        | save_filename save_lineno
          declarator ':' expr_no_commas maybe_attribute
                { $$ = grokfield ($1, $2, $3, current_declspecs, $5);
-                 decl_attributes ($$, $6, prefix_attributes); }
+                 decl_attributes (&$$, chainon ($6, all_prefix_attributes), 0); }
+       | save_filename save_lineno ':' expr_no_commas maybe_attribute
+               { $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4);
+                 decl_attributes (&$$, chainon ($5, all_prefix_attributes), 0); }
+       ;
+
+component_notype_declarator:
+         save_filename save_lineno notype_declarator maybe_attribute
+               { $$ = grokfield ($1, $2, $3, current_declspecs, NULL_TREE);
+                 decl_attributes (&$$, chainon ($4, all_prefix_attributes), 0); }
+       | save_filename save_lineno
+         notype_declarator ':' expr_no_commas maybe_attribute
+               { $$ = grokfield ($1, $2, $3, current_declspecs, $5);
+                 decl_attributes (&$$, chainon ($6, all_prefix_attributes), 0); }
        | save_filename save_lineno ':' expr_no_commas maybe_attribute
                { $$ = grokfield ($1, $2, NULL_TREE, current_declspecs, $4);
-                 decl_attributes ($$, $5, prefix_attributes); }
+                 decl_attributes (&$$, chainon ($5, all_prefix_attributes), 0); }
        ;
 
 /* We chain the enumerators in reverse order.
-   They are put in forward order where enumlist is used.
-   (The order used to be significant, but no longer is so.
-   However, we still maintain the order, just to be clean.)  */
+   They are put in forward order in structsp_attr.  */
 
 enumlist:
          enumerator
@@ -1520,7 +1934,7 @@ enumlist:
                { if ($1 == error_mark_node)
                    $$ = $1;
                  else
-                   $$ = chainon ($3, $1); }
+                   TREE_CHAIN ($3) = $1, $$ = $3; }
        | error
                { $$ = error_mark_node; }
        ;
@@ -1534,10 +1948,11 @@ enumerator:
        ;
 
 typename:
-       typed_typespecs absdcl
-               { $$ = build_tree_list ($1, $2); }
-       | nonempty_type_quals absdcl
-               { $$ = build_tree_list ($1, $2); }
+         declspecs_nosc
+               { pending_xref_error ();
+                 $<ttype>$ = $1; }
+         absdcl
+               { $$ = build_tree_list ($<ttype>2, $3); }
        ;
 
 absdcl:   /* an absolute declarator */
@@ -1546,44 +1961,66 @@ absdcl:   /* an absolute declarator */
        | absdcl1
        ;
 
-nonempty_type_quals:
-         TYPE_QUAL
-               { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
-       | nonempty_type_quals TYPE_QUAL
-               { $$ = tree_cons (NULL_TREE, $2, $1); }
+absdcl_maybe_attribute:   /* absdcl maybe_attribute, but not just attributes */
+       /* empty */
+               { $$ = build_tree_list (build_tree_list (current_declspecs,
+                                                        NULL_TREE),
+                                       all_prefix_attributes); }
+       | absdcl1
+               { $$ = build_tree_list (build_tree_list (current_declspecs,
+                                                        $1),
+                                       all_prefix_attributes); }
+       | absdcl1_noea attributes
+               { $$ = build_tree_list (build_tree_list (current_declspecs,
+                                                        $1),
+                                       chainon ($2, all_prefix_attributes)); }
        ;
 
-type_quals:
-         /* empty */
-               { $$ = NULL_TREE; }
-       | type_quals TYPE_QUAL
-               { $$ = tree_cons (NULL_TREE, $2, $1); }
+absdcl1:  /* a nonempty absolute declarator */
+         absdcl1_ea
+       | absdcl1_noea
        ;
 
-absdcl1:  /* a nonempty absolute declarator */
-         '(' absdcl1 ')'
-               { $$ = $2; }
-         /* `(typedef)1' is `int'.  */
-       | '*' type_quals absdcl1  %prec UNARY
+absdcl1_noea:
+         direct_absdcl1
+       | '*' maybe_type_quals_attrs absdcl1_noea
                { $$ = make_pointer_declarator ($2, $3); }
-       | '*' type_quals  %prec UNARY
+       ;
+
+absdcl1_ea:
+         '*' maybe_type_quals_attrs
                { $$ = make_pointer_declarator ($2, NULL_TREE); }
-       | absdcl1 '(' parmlist  %prec '.'
+       | '*' maybe_type_quals_attrs absdcl1_ea
+               { $$ = make_pointer_declarator ($2, $3); }
+       ;
+
+direct_absdcl1:
+         '(' maybe_attribute absdcl1 ')'
+               { $$ = $2 ? tree_cons ($2, $3, NULL_TREE) : $3; }
+       | direct_absdcl1 '(' parmlist
                { $$ = build_nt (CALL_EXPR, $1, $3, NULL_TREE); }
-       | absdcl1 '[' expr ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, $3); }
-       | absdcl1 '[' ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, $1, NULL_TREE); }
-       | '(' parmlist  %prec '.'
+       | direct_absdcl1 array_declarator
+               { $$ = set_array_declarator_type ($2, $1, 1); }
+       | '(' parmlist
                { $$ = build_nt (CALL_EXPR, NULL_TREE, $2, NULL_TREE); }
-       | '[' expr ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, NULL_TREE, $2); }
-       | '[' ']'  %prec '.'
-               { $$ = build_nt (ARRAY_REF, NULL_TREE, NULL_TREE); }
-       /* ??? It appears we have to support attributes here, however
-          using prefix_attributes is wrong.  */
-       | attributes setattrs absdcl1
-               { $$ = $3; }
+       | array_declarator
+               { $$ = set_array_declarator_type ($1, NULL_TREE, 1); }
+       ;
+
+/* The [...] part of a declarator for an array type.  */
+
+array_declarator:
+       '[' maybe_type_quals_attrs expr ']'
+               { $$ = build_array_declarator ($3, $2, 0, 0); }
+       | '[' maybe_type_quals_attrs ']'
+               { $$ = build_array_declarator (NULL_TREE, $2, 0, 0); }
+       | '[' maybe_type_quals_attrs '*' ']'
+               { $$ = build_array_declarator (NULL_TREE, $2, 0, 1); }
+       | '[' STATIC maybe_type_quals_attrs expr ']'
+               { $$ = build_array_declarator ($4, $3, 1, 0); }
+       /* declspecs_nosc_nots is a synonym for type_quals_attrs.  */
+       | '[' declspecs_nosc_nots STATIC expr ']'
+               { $$ = build_array_declarator ($4, $2, 1, 0); }
        ;
 
 /* A nonempty series of declarations and statements (possibly followed by
@@ -1655,6 +2092,7 @@ end ifobjc
 
 poplevel:  /* empty */
                 { $$ = add_scope_stmt (/*begin_p=*/0, /*partial_p=*/0); }
+        ;
 
 /* Start and end blocks created for the new scopes of C99.  */
 c99_block_start: /* empty */
@@ -1681,8 +2119,8 @@ c99_block_end: /* empty */
                 { if (flag_isoc99)
                    {
                      tree scope_stmt = add_scope_stmt (/*begin_p=*/0, /*partial_p=*/0);
-                     $$ = poplevel (kept_level_p (), 0, 0); 
-                     SCOPE_STMT_BLOCK (TREE_PURPOSE (scope_stmt)) 
+                     $$ = poplevel (kept_level_p (), 0, 0);
+                     SCOPE_STMT_BLOCK (TREE_PURPOSE (scope_stmt))
                        = SCOPE_STMT_BLOCK (TREE_VALUE (scope_stmt))
                        = $$;
                    }
@@ -1725,13 +2163,14 @@ compstmt_or_error:
        ;
 
 compstmt_start: '{' { compstmt_count++;
-                      $$ = c_begin_compound_stmt (); } 
+                      $$ = c_begin_compound_stmt (); }
+        ;
 
 compstmt_nostart: '}'
                { $$ = convert (void_type_node, integer_zero_node); }
        | pushlevel maybe_label_decls compstmt_contents_nonempty '}' poplevel
-               { $$ = poplevel (kept_level_p (), 1, 0); 
-                 SCOPE_STMT_BLOCK (TREE_PURPOSE ($5)) 
+               { $$ = poplevel (kept_level_p (), 1, 0);
+                 SCOPE_STMT_BLOCK (TREE_PURPOSE ($5))
                    = SCOPE_STMT_BLOCK (TREE_VALUE ($5))
                    = $$; }
        ;
@@ -1757,9 +2196,11 @@ compstmt_primary_start:
                  compstmt_count++;
                  $$ = add_stmt (build_stmt (COMPOUND_STMT, last_tree));
                }
+        ;
 
 compstmt: compstmt_start compstmt_nostart
-               { RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); 
+               { RECHAIN_STMTS ($1, COMPOUND_BODY ($1));
+                 last_expr_type = NULL_TREE;
                   $$ = $1; }
        ;
 
@@ -1774,13 +2215,23 @@ simple_if:
        ;
 
 if_prefix:
-         IF '(' expr ')'
-               { c_expand_start_cond (truthvalue_conversion ($3), 
-                                      compstmt_count);
+         /* We must build the IF_STMT node before parsing its
+            condition so that STMT_LINENO refers to the line
+            containing the "if", and not the line containing
+            the close-parenthesis.
+
+            c_begin_if_stmt returns the IF_STMT node, which
+            we later pass to c_expand_start_cond to fill
+            in the condition and other tidbits.  */
+          IF
+                { $<ttype>$ = c_begin_if_stmt (); }
+            '(' expr ')'
+               { c_expand_start_cond (c_common_truthvalue_conversion ($4),
+                                      compstmt_count,$<ttype>2);
                  $<itype>$ = stmt_count;
-                 if_stmt_file = $<filename>-2;
-                 if_stmt_line = $<lineno>-1; }
-       ;
+                 if_stmt_locus.file = $<filename>-2;
+                 if_stmt_locus.line = $<lineno>-1; }
+        ;
 
 /* This is a subroutine of stmt.
    It is used twice, once for valid DO statements
@@ -1789,7 +2240,7 @@ do_stmt_start:
          DO
                { stmt_count++;
                  compstmt_count++;
-                 $<ttype>$ 
+                 $<ttype>$
                    = add_stmt (build_stmt (DO_STMT, NULL_TREE,
                                            NULL_TREE));
                  /* In the event that a parse error prevents
@@ -1814,7 +2265,7 @@ save_filename:
 save_lineno:
                { if (yychar == YYEMPTY)
                    yychar = YYLEX;
-                 $$ = lineno; }
+                 $$ = input_line; }
        ;
 
 lineno_labeled_stmt:
@@ -1837,7 +2288,7 @@ lineno_stmt:
                      /* ??? We currently have no way of recording
                         the filename for a statement.  This probably
                         matters little in practice at the moment,
-                        but I suspect that problems will ocurr when
+                        but I suspect that problems will occur when
                         doing inlining at the tree level.  */
                    }
                }
@@ -1868,36 +2319,47 @@ select_or_iter_stmt:
                     else statement.  Increment stmt_count so we don't
                     give a second error if this is a nested `if'.  */
                  if (extra_warnings && stmt_count++ == $<itype>1)
-                   warning_with_file_and_line (if_stmt_file, if_stmt_line,
-                                               "empty body in an if-statement"); }
+                   warning ("%Hempty body in an if-statement",
+                             &if_stmt_locus); }
 /* Make sure c_expand_end_cond is run once
    for each call to c_expand_start_cond.
    Otherwise a crash is likely.  */
        | simple_if ELSE error
                { c_expand_end_cond (); }
+       /* We must build the WHILE_STMT node before parsing its
+         condition so that STMT_LINENO refers to the line
+         containing the "while", and not the line containing
+         the close-parenthesis.
+
+         c_begin_while_stmt returns the WHILE_STMT node, which
+         we later pass to c_finish_while_stmt_cond to fill
+         in the condition and other tidbits.  */
        | WHILE
-                { stmt_count++; }
+                { stmt_count++;
+                 $<ttype>$ = c_begin_while_stmt (); }
          '(' expr ')'
-                { $4 = truthvalue_conversion ($4);
-                 $<ttype>$ 
-                   = add_stmt (build_stmt (WHILE_STMT, $4, NULL_TREE)); }
+                { $4 = c_common_truthvalue_conversion ($4);
+                 c_finish_while_stmt_cond
+                   (c_common_truthvalue_conversion ($4), $<ttype>2);
+                 $<ttype>$ = add_stmt ($<ttype>2); }
          c99_block_lineno_labeled_stmt
                { RECHAIN_STMTS ($<ttype>6, WHILE_BODY ($<ttype>6)); }
        | do_stmt_start
          '(' expr ')' ';'
-                { DO_COND ($1) = truthvalue_conversion ($3); }
+                { DO_COND ($1) = c_common_truthvalue_conversion ($3); }
        | do_stmt_start error
-               { }
+               { }
        | FOR
                { $<ttype>$ = build_stmt (FOR_STMT, NULL_TREE, NULL_TREE,
                                          NULL_TREE, NULL_TREE);
-                 add_stmt ($<ttype>$); } 
+                 add_stmt ($<ttype>$); }
          '(' for_init_stmt
                { stmt_count++;
                  RECHAIN_STMTS ($<ttype>2, FOR_INIT_STMT ($<ttype>2)); }
          xexpr ';'
-                { if ($6) 
-                   FOR_COND ($<ttype>2) = truthvalue_conversion ($6); }
+                { if ($6)
+                   FOR_COND ($<ttype>2)
+                     = c_common_truthvalue_conversion ($6); }
          xexpr ')'
                { FOR_EXPR ($<ttype>2) = $9; }
          c99_block_lineno_labeled_stmt
@@ -1911,7 +2373,7 @@ select_or_iter_stmt:
 
 for_init_stmt:
          xexpr ';'
-               { add_stmt (build_stmt (EXPR_STMT, $1)); } 
+               { add_stmt (build_stmt (EXPR_STMT, $1)); }
        | decl
                { check_for_loop_decls (); }
        ;
@@ -1941,26 +2403,7 @@ stmt:
                  $$ = c_expand_return ($2); }
        | ASM_KEYWORD maybe_type_qual '(' expr ')' ';'
                { stmt_count++;
-                 STRIP_NOPS ($4);
-                 if ((TREE_CODE ($4) == ADDR_EXPR
-                      && TREE_CODE (TREE_OPERAND ($4, 0)) == STRING_CST)
-                     || TREE_CODE ($4) == STRING_CST)
-                   {
-                     if (TREE_CODE ($4) == ADDR_EXPR)
-                       $4 = TREE_OPERAND ($4, 0);
-                     if (TREE_CHAIN ($4))
-                       $4 = combine_strings ($4);
-                     $$ = add_stmt (build_stmt (ASM_STMT, NULL_TREE, $4,
-                                                NULL_TREE, NULL_TREE,
-                                                NULL_TREE));
-                     ASM_INPUT_P ($$) = 1;
-                   }
-                 else
-                   {
-                     error ("argument of `asm' is not a constant string");
-                     $$ = NULL_TREE;
-                   }
-               }
+                 $$ = simple_asm_stmt ($4); }
        /* This is the case with just output operands.  */
        | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ')' ';'
                { stmt_count++;
@@ -1972,7 +2415,7 @@ stmt:
                  $$ = build_asm_stmt ($2, $4, $6, $8, NULL_TREE); }
        /* This is the case with clobbered registers as well.  */
        | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
-         asm_operands ':' asm_clobbers ')' ';'
+         asm_operands ':' asm_clobbers ')' ';'
                { stmt_count++;
                  $$ = build_asm_stmt ($2, $4, $6, $8, $10); }
        | GOTO identifier ';'
@@ -2015,7 +2458,7 @@ label:      CASE expr_no_commas ':'
                  stmt_count++;
                  if (label)
                    {
-                     decl_attributes (label, $5, NULL_TREE);
+                     decl_attributes (&label, $5, 0);
                      $$ = add_stmt (build_stmt (LABEL_STMT, label));
                    }
                  else
@@ -2027,10 +2470,10 @@ label:    CASE expr_no_commas ':'
 
 maybe_type_qual:
        /* empty */
-               { emit_line_note (input_filename, lineno);
+               { emit_line_note (input_filename, input_line);
                  $$ = NULL_TREE; }
        | TYPE_QUAL
-               { emit_line_note (input_filename, lineno); }
+               { emit_line_note (input_filename, input_line); }
        ;
 
 xexpr:
@@ -2054,24 +2497,32 @@ nonnull_asm_operands:
 
 asm_operand:
          STRING '(' expr ')'
-               { $$ = build_tree_list ($1, $3); }
+               { $$ = build_tree_list (build_tree_list (NULL_TREE, $1), $3); }
+       | '[' identifier ']' STRING '(' expr ')'
+               { $2 = build_string (IDENTIFIER_LENGTH ($2),
+                                    IDENTIFIER_POINTER ($2));
+                 $$ = build_tree_list (build_tree_list ($2, $4), $6); }
        ;
 
 asm_clobbers:
-         string
-               { $$ = tree_cons (NULL_TREE, combine_strings ($1), NULL_TREE); }
-       | asm_clobbers ',' string
-               { $$ = tree_cons (NULL_TREE, combine_strings ($3), $1); }
+         STRING
+               { $$ = tree_cons (NULL_TREE, $1, NULL_TREE); }
+       | asm_clobbers ',' STRING
+               { $$ = tree_cons (NULL_TREE, $3, $1); }
        ;
 \f
 /* This is what appears inside the parens in a function declarator.
-   Its value is a list of ..._TYPE nodes.  */
+   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
                { pushlevel (0);
                  clear_parm_order ();
                  declare_parm_level (0); }
          parmlist_1
-               { $$ = $2;
+               { $$ = $3;
                  parmlist_tags_warning ();
                  poplevel (0, 0, 0); }
        ;
@@ -2086,8 +2537,11 @@ parmlist_1:
                  for (parm = getdecls (); parm; parm = TREE_CHAIN (parm))
                    TREE_ASM_WRITTEN (parm) = 1;
                  clear_parm_order (); }
+         maybe_attribute
+               { /* Dummy action so attributes are in known place
+                    on parser stack.  */ }
          parmlist_1
-               { $$ = $4; }
+               { $$ = $6; }
        | error ')'
                { $$ = tree_cons (NULL_TREE, NULL_TREE, NULL_TREE); }
        ;
@@ -2107,13 +2561,15 @@ parmlist_2:  /* empty */
                  error ("ISO C requires a named argument before `...'");
                }
        | parms
-               { $$ = get_parm_info (1); }
+               { $$ = get_parm_info (1);
+                 parsing_iso_function_signature = true;
+               }
        | parms ',' ELLIPSIS
                { $$ = get_parm_info (0); }
        ;
 
 parms:
-       parm
+       firstparm
                { push_parm_decl ($1); }
        | parms ',' parm
                { push_parm_decl ($3); }
@@ -2122,58 +2578,73 @@ parms:
 /* A single parameter declaration or parameter type name,
    as found in a parmlist.  */
 parm:
-         typed_declspecs setspecs parm_declarator maybe_attribute
+         declspecs_ts setspecs parm_declarator maybe_attribute
+               { $$ = build_tree_list (build_tree_list (current_declspecs,
+                                                        $3),
+                                       chainon ($4, all_prefix_attributes));
+                 POP_DECLSPEC_STACK; }
+       | declspecs_ts setspecs notype_declarator maybe_attribute
                { $$ = build_tree_list (build_tree_list (current_declspecs,
                                                         $3),
-                                       build_tree_list (prefix_attributes,
-                                                        $4));
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | typed_declspecs setspecs notype_declarator maybe_attribute
+                                       chainon ($4, all_prefix_attributes));
+                 POP_DECLSPEC_STACK; }
+       | declspecs_ts setspecs absdcl_maybe_attribute
+               { $$ = $3;
+                 POP_DECLSPEC_STACK; }
+       | declspecs_nots setspecs notype_declarator maybe_attribute
                { $$ = build_tree_list (build_tree_list (current_declspecs,
                                                         $3),
-                                       build_tree_list (prefix_attributes,
-                                                        $4)); 
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | typed_declspecs setspecs absdcl maybe_attribute
+                                       chainon ($4, all_prefix_attributes));
+                 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_tree_list (build_tree_list (current_declspecs,
                                                         $3),
-                                       build_tree_list (prefix_attributes,
-                                                        $4));
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | declmods setspecs notype_declarator maybe_attribute
+                                       chainon ($4, all_prefix_attributes));
+                 POP_DECLSPEC_STACK; }
+       | declspecs_ts_nosa setspecs_fp notype_declarator maybe_attribute
                { $$ = build_tree_list (build_tree_list (current_declspecs,
                                                         $3),
-                                       build_tree_list (prefix_attributes,
-                                                        $4));
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-
-       | declmods setspecs absdcl maybe_attribute
+                                       chainon ($4, all_prefix_attributes));
+                 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_tree_list (build_tree_list (current_declspecs,
                                                         $3),
-                                       build_tree_list (prefix_attributes,
-                                                        $4));
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
+                                       chainon ($4, all_prefix_attributes));
+                 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
                { pushlevel (0);
                  clear_parm_order ();
                  declare_parm_level (1); }
          parmlist_or_identifiers_1
-               { $$ = $2;
+               { $$ = $3;
                  parmlist_tags_warning ();
                  poplevel (0, 0, 0); }
        ;
@@ -2185,7 +2656,15 @@ parmlist_or_identifiers_1:
                  for (t = $1; t; t = TREE_CHAIN (t))
                    if (TREE_VALUE (t) == NULL_TREE)
                      error ("`...' in old-style identifier list");
-                 $$ = tree_cons (NULL_TREE, NULL_TREE, $1); }
+                 $$ = tree_cons (NULL_TREE, NULL_TREE, $1);
+
+                 /* Make sure we have a parmlist after attributes.  */
+                 if ($<ttype>-1 != 0
+                     && (TREE_CODE ($$) != TREE_LIST
+                         || TREE_PURPOSE ($$) == 0
+                         || TREE_CODE (TREE_PURPOSE ($$)) != PARM_DECL))
+                   YYERROR1;
+               }
        ;
 
 /* A nonempty list of identifiers.  */
@@ -2206,9 +2685,11 @@ identifiers_or_typenames:
 
 extension:
        EXTENSION
-               { $$ = SAVE_WARN_FLAGS();
+               { $$ = SAVE_EXT_FLAGS();
                  pedantic = 0;
-                 warn_pointer_arith = 0; }
+                 warn_pointer_arith = 0;
+                 warn_traditional = 0;
+                 flag_iso = 0; }
        ;
 \f
 ifobjc
@@ -2246,12 +2727,14 @@ classdecl:
                {
                  objc_declare_class ($2);
                }
+       ;
 
 aliasdecl:
          ALIAS identifier identifier ';'
                {
                  objc_declare_alias ($2, $3);
                }
+       ;
 
 classdef:
          INTERFACE identifier protocolrefs '{'
@@ -2379,16 +2862,23 @@ classdef:
 protocoldef:
          PROTOCOL identifier protocolrefs
                {
-                 remember_protocol_qualifiers ();
+                 objc_pq_context = 1;
                  objc_interface_context
                    = start_protocol(PROTOCOL_INTERFACE_TYPE, $2, $3);
                }
          methodprotolist END
                {
-                 forget_protocol_qualifiers();
+                 objc_pq_context = 0;
                  finish_protocol(objc_interface_context);
                  objc_interface_context = NULL_TREE;
                }
+       /* The @protocol forward-declaration production introduces a
+          reduce/reduce conflict on ';', which should be resolved in
+          favor of the production 'identifier_list -> identifier'.  */
+       | PROTOCOL identifier_list ';'
+               {
+                 objc_declare_protocols ($2);
+               }
        ;
 
 protocolrefs:
@@ -2444,16 +2934,12 @@ ivar_decls:
    But I am being cautious and not trying it.  */
 
 ivar_decl:
-       typed_typespecs setspecs ivars
+       declspecs_nosc_ts setspecs ivars
                { $$ = $3;
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | nonempty_type_quals setspecs ivars
+                 POP_DECLSPEC_STACK; }
+       | declspecs_nosc_nots setspecs ivars
                { $$ = $3;
-                 current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
+                 POP_DECLSPEC_STACK; }
        | error
                { $$ = NULL_TREE; }
        ;
@@ -2462,7 +2948,7 @@ ivars:
          /* empty */
                { $$ = NULL_TREE; }
        | ivar_declarator
-       | ivars ',' ivar_declarator
+       | ivars ',' maybe_resetattrs ivar_declarator
        ;
 
 ivar_declarator:
@@ -2488,46 +2974,28 @@ ivar_declarator:
                 }
        ;
 
-methoddef:
+methodtype:
          '+'
-               {
-                 remember_protocol_qualifiers ();
-                 if (objc_implementation_context)
-                   objc_inherit_code = CLASS_METHOD_DECL;
-                  else
-                   fatal ("method definition not in class context");
-               }
-         methoddecl
-               {
-                 forget_protocol_qualifiers ();
-                 add_class_method (objc_implementation_context, $3);
-                 start_method_def ($3);
-                 objc_method_context = $3;
-               }
-         optarglist
-               {
-                 continue_method_def ();
-               }
-         compstmt_or_error
-               {
-                 finish_method_def ();
-                 objc_method_context = NULL_TREE;
-               }
-
+               { objc_inherit_code = CLASS_METHOD_DECL; }
        | '-'
+               { objc_inherit_code = INSTANCE_METHOD_DECL; }
+       ;
+
+methoddef:
+         methodtype
                {
-                 remember_protocol_qualifiers ();
-                 if (objc_implementation_context)
-                   objc_inherit_code = INSTANCE_METHOD_DECL;
-                  else
-                   fatal ("method definition not in class context");
+                 objc_pq_context = 1;
+                 if (!objc_implementation_context)
+                   fatal_error ("method definition not in class context");
                }
          methoddecl
                {
-                 forget_protocol_qualifiers ();
-                 add_instance_method (objc_implementation_context, $3);
+                 objc_pq_context = 0;
+                 if (objc_inherit_code == CLASS_METHOD_DECL)
+                   add_class_method (objc_implementation_context, $3);
+                 else
+                   add_instance_method (objc_implementation_context, $3);
                  start_method_def ($3);
-                 objc_method_context = $3;
                }
          optarglist
                {
@@ -2536,7 +3004,6 @@ methoddef:
          compstmt_or_error
                {
                  finish_method_def ();
-                 objc_method_context = NULL_TREE;
                }
        ;
 
@@ -2562,31 +3029,19 @@ semi_or_error:
        ;
 
 methodproto:
-         '+'
-               {
-                 /* Remember protocol qualifiers in prototypes.  */
-                 remember_protocol_qualifiers ();
-                 objc_inherit_code = CLASS_METHOD_DECL;
-               }
-         methoddecl
-               {
-                 /* Forget protocol qualifiers here.  */
-                 forget_protocol_qualifiers ();
-                 add_class_method (objc_interface_context, $3);
-               }
-         semi_or_error
-
-       | '-'
+         methodtype
                {
                  /* Remember protocol qualifiers in prototypes.  */
-                 remember_protocol_qualifiers ();
-                 objc_inherit_code = INSTANCE_METHOD_DECL;
+                 objc_pq_context = 1;
                }
          methoddecl
                {
                  /* Forget protocol qualifiers here.  */
-                 forget_protocol_qualifiers ();
-                 add_instance_method (objc_interface_context, $3);
+                 objc_pq_context = 0;
+                 if (objc_inherit_code == CLASS_METHOD_DECL)
+                   add_class_method (objc_interface_context, $3);
+                 else
+                   add_instance_method (objc_interface_context, $3);
                }
          semi_or_error
        ;
@@ -2637,13 +3092,11 @@ mydecls:
        ;
 
 mydecl:
-       typed_declspecs setspecs myparms ';'
-               { current_declspecs = TREE_VALUE (declspec_stack);
-                 prefix_attributes = TREE_PURPOSE (declspec_stack);
-                 declspec_stack = TREE_CHAIN (declspec_stack); }
-       | typed_declspecs ';'
+       declspecs_ts setspecs myparms ';'
+               { POP_DECLSPEC_STACK; }
+       | declspecs_ts ';'
                { shadow_tag ($1); }
-       | declmods ';'
+       | declspecs_nots ';'
                { pedwarn ("empty declaration"); }
        ;
 
@@ -2661,24 +3114,19 @@ myparm:
          parm_declarator maybe_attribute
                { $$ = build_tree_list (build_tree_list (current_declspecs,
                                                         $1),
-                                       build_tree_list (prefix_attributes,
-                                                        $2)); }
+                                       chainon ($2, all_prefix_attributes)); }
        | notype_declarator maybe_attribute
                { $$ = build_tree_list (build_tree_list (current_declspecs,
                                                         $1),
-                                       build_tree_list (prefix_attributes,
-                                                        $2)); }
-       | absdcl maybe_attribute
-               { $$ = build_tree_list (build_tree_list (current_declspecs,
-                                                        $1),
-                                       build_tree_list (prefix_attributes,
-                                                        $2)); }
+                                       chainon ($2, all_prefix_attributes)); }
+       | absdcl_maybe_attribute
+               { $$ = $1; }
        ;
 
 optparmlist:
          /* empty */
                {
-                 $$ = NULL_TREE;
+                 $$ = NULL_TREE;
                }
        | ',' ELLIPSIS
                {
@@ -2691,7 +3139,7 @@ optparmlist:
                }
          parmlist_2
                {
-                 /* returns a tree list node generated by get_parm_info */
+                 /* returns a tree list node generated by get_parm_info */
                  $$ = $3;
                  poplevel (0, 0, 0);
                }
@@ -2712,8 +3160,9 @@ keywordselector:
 
 selector:
          IDENTIFIER
-        | TYPENAME
-       | OBJECTNAME
+       | TYPENAME
+       | CLASSNAME
+       | OBJECTNAME
        | reservedwords
        ;
 
@@ -2792,14 +3241,8 @@ receiver:
        ;
 
 objcmessageexpr:
-         '['
-               { objc_receiver_context = 1; }
-         receiver
-               { objc_receiver_context = 0; }
-         messageargs ']'
-               {
-                 $$ = build_tree_list ($3, $5);
-               }
+         '[' receiver messageargs ']'
+               { $$ = build_tree_list ($2, $3); }
        ;
 
 selectorarg:
@@ -2867,31 +3310,32 @@ struct resword
 
 /* Disable mask.  Keywords are disabled if (reswords[i].disable & mask) is
    _true_.  */
-#define D_TRAD 0x01    /* not in traditional C */
-#define D_C89  0x02    /* not in C89 */
-#define D_EXT  0x04    /* GCC extension */
-#define D_EXT89        0x08    /* GCC extension incorporated in C99 */
-#define D_OBJC 0x10    /* Objective C only */
-#define D_YES  0x20    /* always starts disabled */
+#define D_C89  0x01    /* not in C89 */
+#define D_EXT  0x02    /* GCC extension */
+#define D_EXT89        0x04    /* GCC extension incorporated in C99 */
+#define D_OBJC 0x08    /* Objective C only */
 
 static const struct resword reswords[] =
 {
   { "_Bool",           RID_BOOL,       0 },
   { "_Complex",                RID_COMPLEX,    0 },
+  { "__FUNCTION__",    RID_FUNCTION_NAME, 0 },
+  { "__PRETTY_FUNCTION__", RID_PRETTY_FUNCTION_NAME, 0 },
   { "__alignof",       RID_ALIGNOF,    0 },
   { "__alignof__",     RID_ALIGNOF,    0 },
   { "__asm",           RID_ASM,        0 },
   { "__asm__",         RID_ASM,        0 },
   { "__attribute",     RID_ATTRIBUTE,  0 },
   { "__attribute__",   RID_ATTRIBUTE,  0 },
-  { "__bounded",       RID_BOUNDED,    0 },
-  { "__bounded__",     RID_BOUNDED,    0 },
+  { "__builtin_choose_expr", RID_CHOOSE_EXPR, 0 },
+  { "__builtin_types_compatible_p", RID_TYPES_COMPATIBLE_P, 0 },
   { "__builtin_va_arg",        RID_VA_ARG,     0 },
   { "__complex",       RID_COMPLEX,    0 },
   { "__complex__",     RID_COMPLEX,    0 },
   { "__const",         RID_CONST,      0 },
   { "__const__",       RID_CONST,      0 },
   { "__extension__",   RID_EXTENSION,  0 },
+  { "__func__",                RID_C99_FUNCTION_NAME, 0 },
   { "__imag",          RID_IMAGPART,   0 },
   { "__imag__",                RID_IMAGPART,   0 },
   { "__inline",                RID_INLINE,     0 },
@@ -2909,10 +3353,9 @@ static const struct resword reswords[] =
   { "__restrict__",    RID_RESTRICT,   0 },
   { "__signed",                RID_SIGNED,     0 },
   { "__signed__",      RID_SIGNED,     0 },
+  { "__thread",                RID_THREAD,     0 },
   { "__typeof",                RID_TYPEOF,     0 },
   { "__typeof__",      RID_TYPEOF,     0 },
-  { "__unbounded",     RID_UNBOUNDED,  0 },
-  { "__unbounded__",   RID_UNBOUNDED,  0 },
   { "__volatile",      RID_VOLATILE,   0 },
   { "__volatile__",    RID_VOLATILE,   0 },
   { "asm",             RID_ASM,        D_EXT },
@@ -2920,7 +3363,7 @@ static const struct resword reswords[] =
   { "break",           RID_BREAK,      0 },
   { "case",            RID_CASE,       0 },
   { "char",            RID_CHAR,       0 },
-  { "const",           RID_CONST,      D_TRAD },
+  { "const",           RID_CONST,      0 },
   { "continue",                RID_CONTINUE,   0 },
   { "default",         RID_DEFAULT,    0 },
   { "do",              RID_DO,         0 },
@@ -2932,45 +3375,51 @@ static const struct resword reswords[] =
   { "for",             RID_FOR,        0 },
   { "goto",            RID_GOTO,       0 },
   { "if",              RID_IF,         0 },
-  { "inline",          RID_INLINE,     D_TRAD|D_EXT89 },
+  { "inline",          RID_INLINE,     D_EXT89 },
   { "int",             RID_INT,        0 },
   { "long",            RID_LONG,       0 },
   { "register",                RID_REGISTER,   0 },
-  { "restrict",                RID_RESTRICT,   D_TRAD|D_C89 },
+  { "restrict",                RID_RESTRICT,   D_C89 },
   { "return",          RID_RETURN,     0 },
   { "short",           RID_SHORT,      0 },
-  { "signed",          RID_SIGNED,     D_TRAD },
+  { "signed",          RID_SIGNED,     0 },
   { "sizeof",          RID_SIZEOF,     0 },
   { "static",          RID_STATIC,     0 },
   { "struct",          RID_STRUCT,     0 },
   { "switch",          RID_SWITCH,     0 },
   { "typedef",         RID_TYPEDEF,    0 },
-  { "typeof",          RID_TYPEOF,     D_TRAD|D_EXT },
+  { "typeof",          RID_TYPEOF,     D_EXT },
   { "union",           RID_UNION,      0 },
   { "unsigned",                RID_UNSIGNED,   0 },
   { "void",            RID_VOID,       0 },
-  { "volatile",                RID_VOLATILE,   D_TRAD },
+  { "volatile",                RID_VOLATILE,   0 },
   { "while",           RID_WHILE,      0 },
 ifobjc
-  { "@class",          RID_AT_CLASS,           D_OBJC },
-  { "@compatibility_alias", RID_AT_ALIAS,      D_OBJC },
-  { "@defs",           RID_AT_DEFS,            D_OBJC },
-  { "@encode",         RID_AT_ENCODE,          D_OBJC },
-  { "@end",            RID_AT_END,             D_OBJC },
-  { "@implementation", RID_AT_IMPLEMENTATION,  D_OBJC },
-  { "@interface",      RID_AT_INTERFACE,       D_OBJC },
-  { "@private",                RID_AT_PRIVATE,         D_OBJC },
-  { "@protected",      RID_AT_PROTECTED,       D_OBJC },
-  { "@protocol",       RID_AT_PROTOCOL,        D_OBJC },
-  { "@public",         RID_AT_PUBLIC,          D_OBJC },
-  { "@selector",       RID_AT_SELECTOR,        D_OBJC },
   { "id",              RID_ID,                 D_OBJC },
-  { "bycopy",          RID_BYCOPY,             D_OBJC|D_YES },
-  { "byref",           RID_BYREF,              D_OBJC|D_YES },
-  { "in",              RID_IN,                 D_OBJC|D_YES },
-  { "inout",           RID_INOUT,              D_OBJC|D_YES },
-  { "oneway",          RID_ONEWAY,             D_OBJC|D_YES },
-  { "out",             RID_OUT,                D_OBJC|D_YES },
+
+  /* These objc keywords are recognized only immediately after
+     an '@'.  */
+  { "class",           RID_AT_CLASS,           D_OBJC },
+  { "compatibility_alias", RID_AT_ALIAS,       D_OBJC },
+  { "defs",            RID_AT_DEFS,            D_OBJC },
+  { "encode",          RID_AT_ENCODE,          D_OBJC },
+  { "end",             RID_AT_END,             D_OBJC },
+  { "implementation",  RID_AT_IMPLEMENTATION,  D_OBJC },
+  { "interface",       RID_AT_INTERFACE,       D_OBJC },
+  { "private",         RID_AT_PRIVATE,         D_OBJC },
+  { "protected",       RID_AT_PROTECTED,       D_OBJC },
+  { "protocol",                RID_AT_PROTOCOL,        D_OBJC },
+  { "public",          RID_AT_PUBLIC,          D_OBJC },
+  { "selector",                RID_AT_SELECTOR,        D_OBJC },
+
+  /* These are recognized only in protocol-qualifier context
+     (see above) */
+  { "bycopy",          RID_BYCOPY,             D_OBJC },
+  { "byref",           RID_BYREF,              D_OBJC },
+  { "in",              RID_IN,                 D_OBJC },
+  { "inout",           RID_INOUT,              D_OBJC },
+  { "oneway",          RID_ONEWAY,             D_OBJC },
+  { "out",             RID_OUT,                D_OBJC },
 end ifobjc
 };
 #define N_reswords (sizeof reswords / sizeof (struct resword))
@@ -2980,7 +3429,7 @@ end ifobjc
    three languages.  */
 static const short rid_to_yy[RID_MAX] =
 {
-  /* RID_STATIC */     SCSPEC,
+  /* RID_STATIC */     STATIC,
   /* RID_UNSIGNED */   TYPESPEC,
   /* RID_LONG */       TYPESPEC,
   /* RID_CONST */      TYPE_QUAL,
@@ -2995,9 +3444,8 @@ static const short rid_to_yy[RID_MAX] =
   /* RID_RESTRICT */   TYPE_QUAL,
 
   /* C extensions */
-  /* RID_BOUNDED */    TYPE_QUAL,
-  /* RID_UNBOUNDED */  TYPE_QUAL,
   /* RID_COMPLEX */    TYPESPEC,
+  /* RID_THREAD */     SCSPEC,
 
   /* C++ */
   /* RID_FRIEND */     0,
@@ -3013,7 +3461,7 @@ static const short rid_to_yy[RID_MAX] =
   /* RID_BYCOPY */     TYPE_QUAL,
   /* RID_BYREF */      TYPE_QUAL,
   /* RID_ONEWAY */     TYPE_QUAL,
-  
+
   /* C */
   /* RID_INT */                TYPESPEC,
   /* RID_CHAR */       TYPESPEC,
@@ -3051,6 +3499,13 @@ static const short rid_to_yy[RID_MAX] =
   /* RID_PTREXTENT */  PTR_EXTENT,
   /* RID_PTRVALUE */   PTR_VALUE,
 
+  /* RID_CHOOSE_EXPR */                        CHOOSE_EXPR,
+  /* RID_TYPES_COMPATIBLE_P */         TYPES_COMPATIBLE_P,
+
+  /* RID_FUNCTION_NAME */              STRING_FUNC_NAME,
+  /* RID_PRETTY_FUNCTION_NAME */       STRING_FUNC_NAME,
+  /* RID_C99_FUNCTION_NAME */          VAR_FUNC_NAME,
+
   /* C++ */
   /* RID_BOOL */       TYPESPEC,
   /* RID_WCHAR */      0,
@@ -3080,19 +3535,6 @@ static const short rid_to_yy[RID_MAX] =
   /* RID_REINTCAST */  0,
   /* RID_STATCAST */   0,
 
-  /* alternate spellings */
-  /* RID_AND */                0,
-  /* RID_AND_EQ */     0,
-  /* RID_NOT */                0,
-  /* RID_NOT_EQ */     0,
-  /* RID_OR */         0,
-  /* RID_OR_EQ */      0,
-  /* RID_XOR */                0,
-  /* RID_XOR_EQ */     0,
-  /* RID_BITAND */     0,
-  /* RID_BITOR */      0,
-  /* RID_COMPL */      0,
-
   /* Objective C */
   /* RID_ID */                 OBJECTNAME,
   /* RID_AT_ENCODE */          ENCODE,
@@ -3114,15 +3556,13 @@ init_reswords ()
 {
   unsigned int i;
   tree id;
-  int mask = ((doing_objc_thang ? 0 : D_OBJC)
-             | (flag_isoc99 ? 0 : D_C89)
-             | (flag_traditional ? D_TRAD : 0)
-             | (flag_no_asm ? (flag_isoc99 ? D_EXT : D_EXT|D_EXT89) : 0));
-
-  /* It is not necessary to register ridpointers as a GC root, because
-     all the trees it points to are permanently interned in the
-     get_identifier hash anyway.  */
-  ridpointers = (tree *) xcalloc ((int) RID_MAX, sizeof (tree));
+  int mask = (flag_isoc99 ? 0 : D_C89)
+             | (flag_no_asm ? (flag_isoc99 ? D_EXT : D_EXT|D_EXT89) : 0);
+
+  if (!flag_objc)
+     mask |= D_OBJC;
+
+  ridpointers = (tree *) ggc_calloc ((int) RID_MAX, sizeof (tree));
   for (i = 0; i < N_reswords; i++)
     {
       /* If a keyword is disabled, do not enter it into the table
@@ -3132,39 +3572,11 @@ init_reswords ()
 
       id = get_identifier (reswords[i].word);
       C_RID_CODE (id) = reswords[i].rid;
+      C_IS_RESERVED_WORD (id) = 1;
       ridpointers [(int) reswords[i].rid] = id;
-
-      /* Objective C does tricky things with enabling and disabling 
-        keywords.  So these we must not elide in the test above, but
-        wait and not mark them reserved now.  */
-      if (! (reswords[i].disable & D_YES))
-       C_IS_RESERVED_WORD (id) = 1;
     }
 }
 
-const char *
-init_parse (filename)
-     const char *filename;
-{
-  add_c_tree_codes ();
-
-  /* Make identifier nodes long enough for the language-specific slots.  */
-  set_identifier_size (sizeof (struct lang_identifier));
-
-  init_reswords ();
-  init_pragma ();
-
-  return init_c_lex (filename);
-}
-
-void
-finish_parse ()
-{
-  cpp_finish (parse_in);
-  /* Call to cpp_destroy () omitted for performance reasons.  */
-  errorcount += cpp_errors (parse_in);
-}
-
 #define NAME(type) cpp_type2name (type)
 
 static void
@@ -3178,19 +3590,16 @@ yyerror (msgid)
   else if (last_token == CPP_CHAR || last_token == CPP_WCHAR)
     {
       unsigned int val = TREE_INT_CST_LOW (yylval.ttype);
-      const char *ell = (last_token == CPP_CHAR) ? "" : "L";
+      const char *const ell = (last_token == CPP_CHAR) ? "" : "L";
       if (val <= UCHAR_MAX && ISGRAPH (val))
        error ("%s before %s'%c'", string, ell, val);
       else
        error ("%s before %s'\\x%x'", string, ell, val);
     }
   else if (last_token == CPP_STRING
-          || last_token == CPP_WSTRING
-          || last_token == CPP_OSTRING)
+          || last_token == CPP_WSTRING)
     error ("%s before string constant", string);
-  else if (last_token == CPP_NUMBER
-          || last_token == CPP_INT
-          || last_token == CPP_FLOAT)
+  else if (last_token == CPP_NUMBER)
     error ("%s before numeric constant", string);
   else if (last_token == CPP_NAME)
     error ("%s before \"%s\"", string, IDENTIFIER_POINTER (yylval.ttype));
@@ -3198,12 +3607,135 @@ yyerror (msgid)
     error ("%s before '%s' token", string, NAME(last_token));
 }
 
+static int
+yylexname ()
+{
+  tree decl;
+
+ifobjc
+  int objc_force_identifier = objc_need_raw_identifier;
+  OBJC_NEED_RAW_IDENTIFIER (0);
+end ifobjc
+
+  if (C_IS_RESERVED_WORD (yylval.ttype))
+    {
+      enum rid rid_code = C_RID_CODE (yylval.ttype);
+
+ifobjc
+      /* Turn non-typedefed refs to "id" into plain identifiers; this
+        allows constructs like "void foo(id id);" to work.  */
+      if (rid_code == RID_ID)
+      {
+       decl = lookup_name (yylval.ttype);
+       if (decl == NULL_TREE || TREE_CODE (decl) != TYPE_DECL)
+         return IDENTIFIER;
+      }
+
+      if (!OBJC_IS_AT_KEYWORD (rid_code)
+         && (!OBJC_IS_PQ_KEYWORD (rid_code) || objc_pq_context))
+end ifobjc
+      {
+       int yycode = rid_to_yy[(int) rid_code];
+       if (yycode == STRING_FUNC_NAME)
+         {
+           /* __FUNCTION__ and __PRETTY_FUNCTION__ get converted
+              to string constants.  */
+           const char *name = fname_string (rid_code);
+
+           yylval.ttype = build_string (strlen (name) + 1, name);
+           C_ARTIFICIAL_STRING_P (yylval.ttype) = 1;
+           last_token = CPP_STRING;  /* so yyerror won't choke */
+           return STRING;
+         }
+
+       /* Return the canonical spelling for this keyword.  */
+       yylval.ttype = ridpointers[(int) rid_code];
+       return yycode;
+      }
+    }
+
+  decl = lookup_name (yylval.ttype);
+  if (decl)
+    {
+      if (TREE_CODE (decl) == TYPE_DECL)
+       return TYPENAME;
+    }
+ifobjc
+  else
+    {
+      tree objc_interface_decl = is_class_name (yylval.ttype);
+      /* ObjC class names are in the same namespace as variables and
+        typedefs, and hence are shadowed by local declarations.  */
+      if (objc_interface_decl
+         && (global_bindings_p ()
+             || (!objc_force_identifier && !decl)))
+       {
+         yylval.ttype = objc_interface_decl;
+         return CLASSNAME;
+       }
+    }
+end ifobjc
+
+  return IDENTIFIER;
+}
+
+/* Concatenate strings before returning them to the parser.  This isn't quite
+   as good as having it done in the lexer, but it's better than nothing.  */
+
+static int
+yylexstring ()
+{
+  enum cpp_ttype next_type;
+  tree orig = yylval.ttype;
+
+  next_type = c_lex (&yylval.ttype);
+  if (next_type == CPP_STRING
+      || next_type == CPP_WSTRING
+      || (next_type == CPP_NAME && yylexname () == STRING))
+    {
+      varray_type strings;
+
+ifc
+      static int last_lineno = 0;
+      static const char *last_input_filename = 0;
+      if (warn_traditional && !in_system_header
+         && (input_line != last_lineno || !last_input_filename ||
+             strcmp (last_input_filename, input_filename)))
+       {
+         warning ("traditional C rejects string concatenation");
+         last_lineno = input_line;
+         last_input_filename = input_filename;
+       }
+end ifc
+
+      VARRAY_TREE_INIT (strings, 32, "strings");
+      VARRAY_PUSH_TREE (strings, orig);
+
+      do
+       {
+         VARRAY_PUSH_TREE (strings, yylval.ttype);
+         next_type = c_lex (&yylval.ttype);
+       }
+      while (next_type == CPP_STRING
+            || next_type == CPP_WSTRING
+            || (next_type == CPP_NAME && yylexname () == STRING));
+
+      yylval.ttype = combine_strings (strings);
+    }
+  else
+    yylval.ttype = orig;
+
+  /* We will have always read one token too many.  */
+  _cpp_backup_tokens (parse_in, 1);
+
+  return STRING;
+}
+
 static inline int
 _yylex ()
 {
retry:
get_next:
   last_token = c_lex (&yylval.ttype);
-
   switch (last_token)
     {
     case CPP_EQ:                                       return '=';
@@ -3225,10 +3757,7 @@ _yylex ()
     case CPP_AND_AND:                                  return ANDAND;
     case CPP_OR_OR:                                    return OROR;
     case CPP_QUERY:                                    return '?';
-    case CPP_COLON:                                    return ':';
-    case CPP_COMMA:                                    return ',';
     case CPP_OPEN_PAREN:                               return '(';
-    case CPP_CLOSE_PAREN:                              return ')';
     case CPP_EQ_EQ:    yylval.code = EQ_EXPR;          return EQCOMPARE;
     case CPP_NOT_EQ:   yylval.code = NE_EXPR;          return EQCOMPARE;
     case CPP_GREATER_EQ:yylval.code = GE_EXPR;         return ARITHCOMPARE;
@@ -3249,7 +3778,6 @@ _yylex ()
     case CPP_CLOSE_SQUARE:                             return ']';
     case CPP_OPEN_BRACE:                               return '{';
     case CPP_CLOSE_BRACE:                              return '}';
-    case CPP_SEMICOLON:                                        return ';';
     case CPP_ELLIPSIS:                                 return ELLIPSIS;
 
     case CPP_PLUS_PLUS:                                        return PLUSPLUS;
@@ -3257,69 +3785,25 @@ _yylex ()
     case CPP_DEREF:                                    return POINTSAT;
     case CPP_DOT:                                      return '.';
 
+      /* The following tokens may affect the interpretation of any
+        identifiers following, if doing Objective-C.  */
+    case CPP_COLON:            OBJC_NEED_RAW_IDENTIFIER (0);   return ':';
+    case CPP_COMMA:            OBJC_NEED_RAW_IDENTIFIER (0);   return ',';
+    case CPP_CLOSE_PAREN:      OBJC_NEED_RAW_IDENTIFIER (0);   return ')';
+    case CPP_SEMICOLON:                OBJC_NEED_RAW_IDENTIFIER (0);   return ';';
+
     case CPP_EOF:
-      if (cpp_pop_buffer (parse_in) == 0)
-       return 0;
-      goto retry;
+      return 0;
 
     case CPP_NAME:
-      if (C_IS_RESERVED_WORD (yylval.ttype))
-       {
-         enum rid rid_code = C_RID_CODE (yylval.ttype);
-         /* Return the canonical spelling for this keyword.  */
-         yylval.ttype = ridpointers[(int) rid_code];
-         return rid_to_yy[(int) rid_code];
-       }
-
-      if (IDENTIFIER_POINTER (yylval.ttype)[0] == '@')
-       {
-         error ("invalid identifier `%s'", IDENTIFIER_POINTER (yylval.ttype));
-         return IDENTIFIER;
-       }
-
       {
-       tree decl;
-
-       decl = lookup_name (yylval.ttype);
-
-       if (decl)
-         {
-           if (TREE_CODE (decl) == TYPE_DECL)
-             return TYPENAME;
-           /* A user-invisible read-only initialized variable
-              should be replaced by its value.
-              We handle only strings since that's the only case used in C.  */
-           else if (TREE_CODE (decl) == VAR_DECL
-                    && DECL_IGNORED_P (decl)
-                    && TREE_READONLY (decl)
-                    && DECL_INITIAL (decl) != 0
-                    && TREE_CODE (DECL_INITIAL (decl)) == STRING_CST)
-             {
-               tree stringval = DECL_INITIAL (decl);
-
-               /* Copy the string value so that we won't clobber anything
-                  if we put something in the TREE_CHAIN of this one.  */
-               yylval.ttype = build_string (TREE_STRING_LENGTH (stringval),
-                                            TREE_STRING_POINTER (stringval));
-               return STRING;
-             }
-         }
-       else if (doing_objc_thang)
-         {
-           tree objc_interface_decl = is_class_name (yylval.ttype);
-
-           if (objc_interface_decl)
-             {
-               yylval.ttype = objc_interface_decl;
-               return CLASSNAME;
-             }
-         }
-
-       return IDENTIFIER;
+       int ret = yylexname ();
+       if (ret == STRING)
+         return yylexstring ();
+       else
+         return ret;
       }
 
-    case CPP_INT:
-    case CPP_FLOAT:
     case CPP_NUMBER:
     case CPP_CHAR:
     case CPP_WCHAR:
@@ -3327,10 +3811,30 @@ _yylex ()
 
     case CPP_STRING:
     case CPP_WSTRING:
-      return STRING;
-      
-    case CPP_OSTRING:
-      return OBJC_STRING;
+      return yylexstring ();
+
+      /* This token is Objective-C specific.  It gives the next token
+        special significance.  */
+    case CPP_ATSIGN:
+ifobjc
+      {
+       tree after_at;
+       enum cpp_ttype after_at_type;
+
+       after_at_type = c_lex (&after_at);
+
+       if (after_at_type == CPP_NAME
+           && C_IS_RESERVED_WORD (after_at)
+           && OBJC_IS_AT_KEYWORD (C_RID_CODE (after_at)))
+         {
+           yylval.ttype = after_at;
+           last_token = after_at_type;
+           return rid_to_yy [(int) C_RID_CODE (after_at)];
+         }
+       _cpp_backup_tokens (parse_in, 1);
+       return '@';
+      }
+end ifobjc
 
       /* These tokens are C++ specific (and will not be generated
          in C mode, but let's be cautious).  */
@@ -3344,13 +3848,12 @@ _yylex ()
       /* These tokens should not survive translation phase 4.  */
     case CPP_HASH:
     case CPP_PASTE:
-      error ("syntax error before '%s' token", NAME(last_token));
-      goto retry;
+      error ("syntax error at '%s' token", NAME(last_token));
+      goto get_next;
 
     default:
       abort ();
     }
-
   /* NOTREACHED */
 }
 
@@ -3364,21 +3867,6 @@ yylex()
   return r;
 }
 
-/* Sets the value of the 'yydebug' variable to VALUE.
-   This is a function so we don't have to have YYDEBUG defined
-   in order to build the compiler.  */
-
-void
-set_yydebug (value)
-     int value;
-{
-#if YYDEBUG != 0
-  yydebug = value;
-#else
-  warning ("YYDEBUG not defined.");
-#endif
-}
-
 /* Function used when yydebug is set, to print a token in more detail.  */
 
 static void
@@ -3390,7 +3878,7 @@ yyprint (file, yychar, yyl)
   tree t = yyl.ttype;
 
   fprintf (file, " [%s]", NAME(last_token));
-  
+
   switch (yychar)
     {
     case IDENTIFIER:
@@ -3399,6 +3887,7 @@ yyprint (file, yychar, yyl)
     case TYPESPEC:
     case TYPE_QUAL:
     case SCSPEC:
+    case STATIC:
       if (IDENTIFIER_POINTER (t))
        fprintf (file, " `%s'", IDENTIFIER_POINTER (t));
       break;
@@ -3406,25 +3895,11 @@ yyprint (file, yychar, yyl)
     case CONSTANT:
       fprintf (file, " %s", GET_MODE_NAME (TYPE_MODE (TREE_TYPE (t))));
       if (TREE_CODE (t) == INTEGER_CST)
-       fprintf (file,
-#if HOST_BITS_PER_WIDE_INT == 64
-#if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_INT
-                " 0x%x%016x",
-#else
-#if HOST_BITS_PER_WIDE_INT == HOST_BITS_PER_LONG
-                " 0x%lx%016lx",
-#else
-                " 0x%llx%016llx",
-#endif
-#endif
-#else
-#if HOST_BITS_PER_WIDE_INT != HOST_BITS_PER_INT
-                " 0x%lx%08lx",
-#else
-                " 0x%x%08x",
-#endif
-#endif
-                TREE_INT_CST_HIGH (t), TREE_INT_CST_LOW (t));
+       {
+         fputs (" ", file);
+         fprintf (file, HOST_WIDE_INT_PRINT_DOUBLE_HEX,
+                  TREE_INT_CST_HIGH (t), TREE_INT_CST_LOW (t));
+       }
       break;
     }
 }
@@ -3432,17 +3907,16 @@ yyprint (file, yychar, yyl)
 /* This is not the ideal place to put these, but we have to get them out
    of c-lex.c because cp/lex.c has its own versions.  */
 
-/* Return something to represent absolute declarators containing a *.
-   TARGET is the absolute declarator that the * contains.
-   TYPE_QUALS is a list of modifiers such as const or volatile
-   to apply to the pointer type, represented as identifiers.
-
-   We return an INDIRECT_REF whose "contents" are TARGET
-   and whose type is the modifier list.  */
+/* Free malloced parser stacks if necessary.  */
 
-tree
-make_pointer_declarator (type_quals, target)
-     tree type_quals, target;
+void
+free_parser_stacks ()
 {
-  return build1 (INDIRECT_REF, type_quals, target);
+  if (malloced_yyss)
+    {
+      free (malloced_yyss);
+      free (malloced_yyvs);
+    }
 }
+
+#include "gt-c-parse.h"