OSDN Git Service

* Makefile.in (local-distclean): Also remove fastjar.
[pf3gnuchains/gcc-fork.git] / gcc / c-parse.in
index bd9e652..cf010e6 100644 (file)
@@ -72,14 +72,17 @@ end ifc
 /* Like YYERROR but do call yyerror.  */
 #define YYERROR1 { yyerror ("syntax error"); YYERROR; }
 
-/* Cause the `yydebug' variable to be defined.  */
+/* 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
 %}
 
 %start program
 
 %union {long itype; tree ttype; enum tree_code code;
-       const char *filename; int lineno; int ends_in_label; }
+       const char *filename; int lineno; }
 
 /* All identifiers that are not reserved words
    and are not declared typedefs in the current block */
@@ -173,8 +176,10 @@ end ifc
 %type <ttype> maybe_attribute attributes attribute attribute_list attrib
 %type <ttype> any_word extension
 
-%type <ttype> compstmt compstmt_nostart compstmt_primary_start
+%type <ttype> compstmt compstmt_start compstmt_nostart compstmt_primary_start
+%type <ttype> do_stmt_start poplevel
 
+%type <ttype> c99_block_start c99_block_end
 %type <ttype> declarator
 %type <ttype> notype_declarator after_type_declarator
 %type <ttype> parm_declarator
@@ -192,8 +197,6 @@ end ifc
 
 %type <itype> setspecs
 
-%type <ends_in_label> lineno_stmt_or_label lineno_stmt_or_labels stmt_or_label
-
 %type <filename> save_filename
 %type <lineno> save_lineno
 \f
@@ -511,8 +514,6 @@ unary_expr:
                { $$ = build_unary_op (REALPART_EXPR, $2, 0); }
        | IMAGPART cast_expr %prec UNARY
                { $$ = build_unary_op (IMAGPART_EXPR, $2, 0); }
-       | VA_ARG '(' expr_no_commas ',' typename ')'
-               { $$ = build_va_arg ($3, groktypename ($5)); }
        ;
 
 sizeof:
@@ -661,37 +662,32 @@ primary:
        | '(' error ')'
                { $$ = error_mark_node; }
        | compstmt_primary_start compstmt_nostart ')'
-               { tree rtl_exp;
-                 if (pedantic)
-                   pedwarn ("ISO C forbids braced-groups within expressions");
+                 { tree saved_last_tree;
+
+                  if (pedantic)
+                    pedwarn ("ISO C forbids braced-groups within expressions");
                  pop_label_level ();
-                 rtl_exp = expand_end_stmt_expr ($1);
-                 /* The statements have side effects, so the group does.  */
-                 TREE_SIDE_EFFECTS (rtl_exp) = 1;
 
-                 if (TREE_CODE ($2) == BLOCK)
-                   {
-                     /* Make a BIND_EXPR for the BLOCK already made.  */
-                     $$ = build (BIND_EXPR, TREE_TYPE (rtl_exp),
-                                 NULL_TREE, rtl_exp, $2);
-                     /* Remove the block from the tree at this point.
-                        It gets put back at the proper place
-                        when the BIND_EXPR is expanded.  */
-                     delete_block ($2);
-                   }
-                 else
-                   $$ = $2;
+                 saved_last_tree = COMPOUND_BODY ($1);
+                 RECHAIN_STMTS ($1, COMPOUND_BODY ($1));
+                 last_tree = saved_last_tree;
+                 TREE_CHAIN (last_tree) = NULL_TREE;
+                 if (!last_expr_type)
+                   last_expr_type = void_type_node;
+                 $$ = build1 (STMT_EXPR, last_expr_type, $1);
+                 TREE_SIDE_EFFECTS ($$) = 1;
                }
        | compstmt_primary_start error ')'
                {
-                 /* Make sure we call expand_end_stmt_expr.  Otherwise
-                    we are likely to lose sequences and crash later.  */
                  pop_label_level ();
-                 expand_end_stmt_expr ($1);
+                 last_tree = COMPOUND_BODY ($1);
+                 TREE_CHAIN (last_tree) = NULL_TREE;
                  $$ = error_mark_node;
                }
        | primary '(' exprlist ')'   %prec '.'
                { $$ = build_function_call ($1, $3); }
+       | VA_ARG '(' expr_no_commas ',' typename ')'
+               { $$ = build_va_arg ($3, groktypename ($5)); }
        | primary '[' expr ']'   %prec '.'
                { $$ = build_array_ref ($1, $3); }
        | primary '.' identifier
@@ -829,13 +825,6 @@ lineno_decl:
                { }
        ;
 
-decls:
-       lineno_decl
-       | errstmt
-       | decls lineno_decl
-       | lineno_decl errstmt
-       ;
-
 /* records the type and storage class specs to use for processing
    the declarators that follow.
    Maintains a stack of outer-level values of current_declspecs,
@@ -1138,9 +1127,15 @@ initlist1:
    It may use braces.  */
 initelt:
          designator_list '=' initval
+               { if (pedantic && ! flag_isoc99)
+                   pedwarn ("ISO C89 forbids specifying subobject to initialize"); }
        | designator initval
+               { if (pedantic)
+                   pedwarn ("obsolete use of designated initializer without `='"); }
        | identifier ':'
-               { set_init_label ($1); }
+               { set_init_label ($1);
+                 if (pedantic)
+                   pedwarn ("obsolete use of designated initializer with `:'"); }
          initval
        | initval
        ;
@@ -1168,7 +1163,9 @@ designator:
           so don't include these productions in the Objective-C grammar.  */
 ifc
        | '[' expr_no_commas ELLIPSIS expr_no_commas ']'
-               { set_init_index ($2, $4); }
+               { 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
@@ -1196,8 +1193,10 @@ nested_function:
    There followed a repeated execution of that same rule,
    which called YYERROR1 again, and so on.  */
          compstmt
-               { finish_function (1);
-                 pop_function_context (); }
+               { tree decl = current_function_decl;
+                 finish_function (1);
+                 pop_function_context (); 
+                 add_decl_stmt (decl); }
        ;
 
 notype_nested_function:
@@ -1222,8 +1221,10 @@ notype_nested_function:
    There followed a repeated execution of that same rule,
    which called YYERROR1 again, and so on.  */
          compstmt
-               { finish_function (1);
-                 pop_function_context (); }
+               { tree decl = current_function_decl;
+                 finish_function (1);
+                 pop_function_context (); 
+                 add_decl_stmt (decl); }
        ;
 
 /* Any kind of declarator (thus, all declarators allowed
@@ -1575,39 +1576,66 @@ absdcl1:  /* a nonempty absolute declarator */
                { $$ = $3; }
        ;
 
-/* at least one statement, the first of which parses without error.  */
-/* stmts is used only after decls, so an invalid first statement
-   is actually regarded as an invalid decl and part of the decls.  */
+/* A nonempty series of declarations and statements (possibly followed by
+   some labels) that can form the body of a compound statement.
+   NOTE: we don't allow labels on declarations; this might seem like a
+   natural extension, but there would be a conflict between attributes
+   on the label and prefix attributes on the declaration.  */
 
-stmts:
-       lineno_stmt_or_labels
+stmts_and_decls:
+         lineno_stmt_decl_or_labels_ending_stmt
+       | lineno_stmt_decl_or_labels_ending_decl
+       | lineno_stmt_decl_or_labels_ending_label
                {
-                 if (pedantic && $1)
-                   pedwarn ("ISO C forbids label at end of compound statement");
+                 pedwarn ("deprecated use of label at end of compound statement");
                }
+       | lineno_stmt_decl_or_labels_ending_error
        ;
 
-lineno_stmt_or_labels:
-         lineno_stmt_or_label
-       | lineno_stmt_or_labels lineno_stmt_or_label
-               { $$ = $2; }
-       | lineno_stmt_or_labels errstmt
-               { $$ = 0; }
+lineno_stmt_decl_or_labels_ending_stmt:
+         lineno_stmt
+       | lineno_stmt_decl_or_labels_ending_stmt lineno_stmt
+       | lineno_stmt_decl_or_labels_ending_decl lineno_stmt
+       | lineno_stmt_decl_or_labels_ending_label lineno_stmt
+       | lineno_stmt_decl_or_labels_ending_error lineno_stmt
        ;
 
-xstmts:
-       /* empty */
-       | stmts
+lineno_stmt_decl_or_labels_ending_decl:
+         lineno_decl
+       | lineno_stmt_decl_or_labels_ending_stmt lineno_decl
+               { if (pedantic && !flag_isoc99)
+                   pedwarn ("ISO C89 forbids mixed declarations and code"); }
+       | lineno_stmt_decl_or_labels_ending_decl lineno_decl
+       | lineno_stmt_decl_or_labels_ending_error lineno_decl
+       ;
+
+lineno_stmt_decl_or_labels_ending_label:
+         lineno_label
+       | lineno_stmt_decl_or_labels_ending_stmt lineno_label
+       | lineno_stmt_decl_or_labels_ending_decl lineno_label
+       | lineno_stmt_decl_or_labels_ending_label lineno_label
+       | lineno_stmt_decl_or_labels_ending_error lineno_label
+       ;
+
+lineno_stmt_decl_or_labels_ending_error:
+       errstmt
+       | lineno_stmt_decl_or_labels errstmt
+       ;
+
+lineno_stmt_decl_or_labels:
+         lineno_stmt_decl_or_labels_ending_stmt
+       | lineno_stmt_decl_or_labels_ending_decl
+       | lineno_stmt_decl_or_labels_ending_label
+       | lineno_stmt_decl_or_labels_ending_error
        ;
 
 errstmt:  error ';'
        ;
 
 pushlevel:  /* empty */
-               { emit_line_note (input_filename, lineno);
-                 pushlevel (0);
+               { pushlevel (0);
                  clear_last_expr ();
-                 expand_start_bindings (0);
+                 add_scope_stmt (/*begin_p=*/1, /*partial_p=*/0);
 ifobjc
                  if (objc_method_context)
                    add_objc_decls ();
@@ -1615,6 +1643,43 @@ 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 */
+               { if (flag_isoc99)
+                   {
+                     $$ = c_begin_compound_stmt ();
+                     pushlevel (0);
+                     clear_last_expr ();
+                     add_scope_stmt (/*begin_p=*/1, /*partial_p=*/0);
+ifobjc
+                     if (objc_method_context)
+                       add_objc_decls ();
+end ifobjc
+                   }
+                 else
+                   $$ = NULL_TREE;
+               }
+       ;
+
+/* Productions using c99_block_start and c99_block_end will need to do what's
+   in compstmt: RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); $$ = $2; where
+   $1 is the value of c99_block_start and $2 of c99_block_end.  */
+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)) 
+                       = SCOPE_STMT_BLOCK (TREE_VALUE (scope_stmt))
+                       = $$;
+                   }
+                 else
+                   $$ = NULL_TREE; }
+       ;
+
 /* Read zero or more forward-declarations for labels
    that nested functions can jump to.  */
 maybe_label_decls:
@@ -1636,7 +1701,7 @@ label_decl:
                    {
                      tree label = shadow_label (TREE_VALUE (link));
                      C_DECLARED_LABEL_FLAG (label) = 1;
-                     declare_nonlocal_label (label);
+                     add_decl_stmt (label);
                    }
                }
        ;
@@ -1649,22 +1714,21 @@ compstmt_or_error:
        | error compstmt
        ;
 
-compstmt_start: '{' { compstmt_count++; }
+compstmt_start: '{' { compstmt_count++;
+                      $$ = c_begin_compound_stmt (); } 
 
 compstmt_nostart: '}'
                { $$ = convert (void_type_node, integer_zero_node); }
-       | pushlevel maybe_label_decls decls xstmts '}'
-               { emit_line_note (input_filename, lineno);
-                 expand_end_bindings (getdecls (), 1, 0);
-                 $$ = poplevel (1, 1, 0); }
-       | pushlevel maybe_label_decls error '}'
-               { emit_line_note (input_filename, lineno);
-                 expand_end_bindings (getdecls (), kept_level_p (), 0);
-                 $$ = poplevel (kept_level_p (), 0, 0); }
-       | pushlevel maybe_label_decls stmts '}'
-               { emit_line_note (input_filename, lineno);
-                 expand_end_bindings (getdecls (), kept_level_p (), 0);
-                 $$ = poplevel (kept_level_p (), 0, 0); }
+       | pushlevel maybe_label_decls compstmt_contents_nonempty '}' poplevel
+               { $$ = poplevel (kept_level_p (), 1, 0); 
+                 SCOPE_STMT_BLOCK (TREE_PURPOSE ($5)) 
+                   = SCOPE_STMT_BLOCK (TREE_VALUE ($5))
+                   = $$; }
+       ;
+
+compstmt_contents_nonempty:
+         stmts_and_decls
+       | error
        ;
 
 compstmt_primary_start:
@@ -1680,17 +1744,19 @@ compstmt_primary_start:
                     that are contained in it.  */
                  keep_next_level ();
                  push_label_level ();
-                 $$ = expand_start_stmt_expr ();
                  compstmt_count++;
+                 $$ = add_stmt (build_stmt (COMPOUND_STMT, last_tree));
                }
 
 compstmt: compstmt_start compstmt_nostart
-               { $$ = $2; }
+               { RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); 
+                  $$ = $2; }
        ;
 
 /* Value is number of statements counted as of the closeparen.  */
 simple_if:
-         if_prefix lineno_labeled_stmt
+         if_prefix c99_block_lineno_labeled_stmt
+                { c_finish_then (); }
 /* Make sure c_expand_end_cond is run once
    for each call to c_expand_start_cond.
    Otherwise a crash is likely.  */
@@ -1699,12 +1765,11 @@ simple_if:
 
 if_prefix:
          IF '(' expr ')'
-               { emit_line_note ($<filename>-1, $<lineno>0);
-                 c_expand_start_cond (truthvalue_conversion ($3), 0, 
+               { c_expand_start_cond (truthvalue_conversion ($3), 
                                       compstmt_count);
                  $<itype>$ = stmt_count;
-                 if_stmt_file = $<filename>-1;
-                 if_stmt_line = $<lineno>0; }
+                 if_stmt_file = $<filename>-2;
+                 if_stmt_line = $<lineno>-1; }
        ;
 
 /* This is a subroutine of stmt.
@@ -1714,12 +1779,17 @@ do_stmt_start:
          DO
                { stmt_count++;
                  compstmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
-                 /* See comment in `while' alternative, above.  */
-                 emit_nop ();
-                 expand_start_loop_continue_elsewhere (1); }
-         lineno_labeled_stmt WHILE
-               { expand_loop_continue_here (); }
+                 $<ttype>$ 
+                   = add_stmt (build_stmt (DO_STMT, NULL_TREE,
+                                           NULL_TREE));
+                 /* In the event that a parse error prevents
+                    parsing the complete do-statement, set the
+                    condition now.  Otherwise, we can get crashes at
+                    RTL-generation time.  */
+                 DO_COND ($<ttype>$) = error_mark_node; }
+         c99_block_lineno_labeled_stmt WHILE
+               { $$ = $<ttype>2;
+                 RECHAIN_STMTS ($$, DO_BODY ($$)); }
        ;
 
 /* The forced readahead in here is because we might be at the end of a
@@ -1747,43 +1817,30 @@ lineno_labeled_stmt:
                { }
        ;
 
-lineno_stmt_or_label:
-         save_filename save_lineno stmt_or_label
-               { $$ = $3; }
+/* Like lineno_labeled_stmt, but a block in C99.  */
+c99_block_lineno_labeled_stmt:
+         c99_block_start lineno_labeled_stmt c99_block_end
+               { if (flag_isoc99)
+                   RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); }
        ;
 
-stmt_or_label:
-         stmt
-               { $$ = 0; }
-       | label
-               { $$ = 1; }
+lineno_stmt:
+         save_filename save_lineno stmt
+               { }
        ;
 
-/* Parse a single real statement, not including any labels.  */
-stmt:
-         compstmt
-               { stmt_count++; }
-       | expr ';'
-               { stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
-/* It appears that this should not be done--that a non-lvalue array
-   shouldn't get an error if the value isn't used.
-   Section 3.2.2.1 says that an array lvalue gets converted to a pointer
-   if it appears as a top-level expression,
-   but says nothing about non-lvalue arrays.  */
-#if 0
-                 /* Call default_conversion to get an error
-                    on referring to a register array if pedantic.  */
-                 if (TREE_CODE (TREE_TYPE ($1)) == ARRAY_TYPE
-                     || TREE_CODE (TREE_TYPE ($1)) == FUNCTION_TYPE)
-                   $1 = default_conversion ($1);
-#endif
-                 expand_expr_stmt ($1); }
-       | simple_if ELSE
+lineno_label:
+         save_filename save_lineno label
+               { }
+       ;
+
+select_or_iter_stmt:
+         simple_if ELSE
                { c_expand_start_else ();
                  $<itype>1 = stmt_count; }
-         lineno_labeled_stmt
-               { c_expand_end_cond ();
+         c99_block_lineno_labeled_stmt
+                { c_finish_else ();
+                 c_expand_end_cond ();
                  if (extra_warnings && stmt_count == $<itype>1)
                    warning ("empty body in an else-statement"); }
        | simple_if %prec IF
@@ -1801,83 +1858,61 @@ stmt:
        | simple_if ELSE error
                { c_expand_end_cond (); }
        | WHILE
-               { stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
-                 /* The emit_nop used to come before emit_line_note,
-                    but that made the nop seem like part of the preceding line.
-                    And that was confusing when the preceding line was
-                    inside of an if statement and was not really executed.
-                    I think it ought to work to put the nop after the line number.
-                    We will see.  --rms, July 15, 1991.  */
-                 emit_nop (); }
+                { stmt_count++; }
          '(' expr ')'
-               { /* Don't start the loop till we have succeeded
-                    in parsing the end test.  This is to make sure
-                    that we end every loop we start.  */
-                 expand_start_loop (1);
-                 emit_line_note (input_filename, lineno);
-                 expand_exit_loop_if_false (NULL_PTR,
-                                            truthvalue_conversion ($4)); }
-         lineno_labeled_stmt
-               { expand_end_loop (); }
+                { $4 = truthvalue_conversion ($4);
+                 $<ttype>$ 
+                   = add_stmt (build_stmt (WHILE_STMT, $4, NULL_TREE)); }
+         c99_block_lineno_labeled_stmt
+               { RECHAIN_STMTS ($<ttype>6, WHILE_BODY ($<ttype>6)); }
        | do_stmt_start
          '(' expr ')' ';'
-               { emit_line_note (input_filename, lineno);
-                 expand_exit_loop_if_false (NULL_PTR,
-                                            truthvalue_conversion ($3));
-                 expand_end_loop (); }
-/* This rule is needed to make sure we end every loop we start.  */
+                { DO_COND ($1) = truthvalue_conversion ($3); }
        | do_stmt_start error
-               { expand_end_loop (); }
+               { }
        | FOR
-         '(' xexpr ';'
+               { $<ttype>$ = build_stmt (FOR_STMT, NULL_TREE, NULL_TREE,
+                                         NULL_TREE, NULL_TREE);
+                 add_stmt ($<ttype>$); } 
+         '(' for_init_stmt
                { stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
-                 /* See comment in `while' alternative, above.  */
-                 emit_nop ();
-                 if ($3) c_expand_expr_stmt ($3);
-                 /* Next step is to call expand_start_loop_continue_elsewhere,
-                    but wait till after we parse the entire for (...).
-                    Otherwise, invalid input might cause us to call that
-                    fn without calling expand_end_loop.  */
-               }
+                 RECHAIN_STMTS ($<ttype>2, FOR_INIT_STMT ($<ttype>2)); }
          xexpr ';'
-               /* Can't emit now; wait till after expand_start_loop...  */
-               { $<lineno>7 = lineno;
-                 $<filename>$ = input_filename; }
+                { FOR_COND ($<ttype>2) = $6; }
          xexpr ')'
-               { 
-                 /* Start the loop.  Doing this after parsing
-                    all the expressions ensures we will end the loop.  */
-                 expand_start_loop_continue_elsewhere (1);
-                 /* Emit the end-test, with a line number.  */
-                 emit_line_note ($<filename>8, $<lineno>7);
-                 if ($6)
-                   expand_exit_loop_if_false (NULL_PTR,
-                                              truthvalue_conversion ($6));
-                 $<lineno>7 = lineno;
-                 $<filename>8 = input_filename; }
-         lineno_labeled_stmt
-               { /* Emit the increment expression, with a line number.  */
-                 emit_line_note ($<filename>8, $<lineno>7);
-                 expand_loop_continue_here ();
-                 if ($9)
-                   c_expand_expr_stmt ($9);
-                 expand_end_loop (); }
+               { FOR_EXPR ($<ttype>2) = $9; }
+         c99_block_lineno_labeled_stmt
+                { RECHAIN_STMTS ($<ttype>2, FOR_BODY ($<ttype>2)); }
        | SWITCH '(' expr ')'
                { stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
-                 c_expand_start_case ($3); }
-         lineno_labeled_stmt
-               { expand_end_case ($3); }
+                 $<ttype>$ = c_start_case ($3); }
+         c99_block_lineno_labeled_stmt
+                { c_finish_case (); }
+       ;
+
+for_init_stmt:
+         xexpr ';'
+               { add_stmt (build_stmt (EXPR_STMT, $1)); } 
+       | decl
+               { check_for_loop_decls (); }
+       ;
+
+/* Parse a single real statement, not including any labels.  */
+stmt:
+         compstmt
+               { stmt_count++; }
+       | expr ';'
+               { stmt_count++;
+                 c_expand_expr_stmt ($1); }
+       | c99_block_start select_or_iter_stmt c99_block_end
+               { if (flag_isoc99)
+                   RECHAIN_STMTS ($1, COMPOUND_BODY ($1)); }
        | BREAK ';'
-               { build_break_stmt ();
-                 stmt_count++;
-                 genrtl_break_stmt (); }
+               { stmt_count++;
+                 add_stmt (build_break_stmt ()); }
        | CONTINUE ';'
-                { build_continue_stmt ();
-                  stmt_count++;
-                 genrtl_continue_stmt (); }
+                { stmt_count++;
+                 add_stmt (build_continue_stmt ()); }
        | RETURN ';'
                 { stmt_count++;
                  c_expand_return (NULL_TREE); }
@@ -1886,25 +1921,29 @@ stmt:
                  c_expand_return ($2); }
        | ASM_KEYWORD maybe_type_qual '(' expr ')' ';'
                { stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
                  STRIP_NOPS ($4);
                  if ((TREE_CODE ($4) == ADDR_EXPR
                       && TREE_CODE (TREE_OPERAND ($4, 0)) == STRING_CST)
                      || TREE_CODE ($4) == STRING_CST)
-                   expand_asm ($4);
+                   {
+                     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));
+                   }
                  else
                    error ("argument of `asm' is not a constant string"); }
        /* This is the case with just output operands.  */
        | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ')' ';'
                { stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
                  c_expand_asm_operands ($4, $6, NULL_TREE, NULL_TREE,
                                         $2 == ridpointers[(int)RID_VOLATILE],
                                         input_filename, lineno); }
        /* This is the case with input operands as well.  */
        | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':' asm_operands ')' ';'
                { stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
                  c_expand_asm_operands ($4, $6, $8, NULL_TREE,
                                         $2 == ridpointers[(int)RID_VOLATILE],
                                         input_filename, lineno); }
@@ -1912,27 +1951,25 @@ stmt:
        | ASM_KEYWORD maybe_type_qual '(' expr ':' asm_operands ':'
          asm_operands ':' asm_clobbers ')' ';'
                { stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
                  c_expand_asm_operands ($4, $6, $8, $10,
                                         $2 == ridpointers[(int)RID_VOLATILE],
                                         input_filename, lineno); }
        | GOTO identifier ';'
                { tree decl;
                  stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
                  decl = lookup_label ($2);
                  if (decl != 0)
                    {
                      TREE_USED (decl) = 1;
-                     expand_goto (decl);
+                     add_stmt (build_stmt (GOTO_STMT, decl));
                    }
                }
        | GOTO '*' expr ';'
                { if (pedantic)
                    pedwarn ("ISO C forbids `goto *expr;'");
                  stmt_count++;
-                 emit_line_note ($<filename>-1, $<lineno>0);
-                 expand_computed_goto (convert (ptr_type_node, $3)); }
+                 $3 = convert (ptr_type_node, $3);
+                 add_stmt (build_stmt (GOTO_STMT, $3)); }
        | ';'
        ;
 
@@ -1952,11 +1989,10 @@ label:    CASE expr_no_commas ':'
        | identifier save_filename save_lineno ':' maybe_attribute
                { tree label = define_label ($2, $3, $1);
                  stmt_count++;
-                 emit_nop ();
                  if (label)
                    {
-                     expand_label (label);
                      decl_attributes (label, $5, NULL_TREE);
+                     add_stmt (build_stmt (LABEL_STMT, label));
                    }
                }
        ;
@@ -2794,9 +2830,6 @@ end ifobjc
    cpplib.h's token codes into yacc's token codes.  */
 
 static enum cpp_ttype last_token;
-#if USE_CPPLIB
-extern cpp_reader parse_in;
-#endif
 
 /* The reserved keyword table.  */
 struct resword
@@ -2817,6 +2850,8 @@ struct resword
 
 static const struct resword reswords[] =
 {
+  { "_Bool",           RID_BOOL,       0 },
+  { "_Complex",                RID_COMPLEX,    0 },
   { "__alignof",       RID_ALIGNOF,    0 },
   { "__alignof__",     RID_ALIGNOF,    0 },
   { "__asm",           RID_ASM,        0 },
@@ -2991,7 +3026,7 @@ static const short rid_to_yy[RID_MAX] =
   /* RID_PTRVALUE */   PTR_VALUE,
 
   /* C++ */
-  /* RID_BOOL */       0,
+  /* RID_BOOL */       TYPESPEC,
   /* RID_WCHAR */      0,
   /* RID_CLASS */      0,
   /* RID_PUBLIC */     0,
@@ -3099,25 +3134,11 @@ init_parse (filename)
 void
 finish_parse ()
 {
-#if USE_CPPLIB
-  cpp_finish (&parse_in, 0 /* no printer */);
-  errorcount += parse_in.errors;
-#else
-  fclose (finput);
-#endif
+  cpp_finish (parse_in);
+  errorcount += parse_in->errors;
 }
 
-#if USE_CPPLIB
 #define NAME(type) cpp_type2name (type)
-#else
-/* Bleah */
-#include "symcat.h"
-#define OP(e, s) s,
-#define TK(e, s) STRINGX(e),
-
-static const char *type2name[N_TTYPES] = { TTYPE_TABLE };
-#define NAME(type) type2name[type]
-#endif
 
 static void
 yyerror (msgid)
@@ -3210,10 +3231,8 @@ _yylex ()
     case CPP_DOT:                                      return '.';
 
     case CPP_EOF:
-#if USE_CPPLIB
-      cpp_pop_buffer (&parse_in);
-      if (! CPP_BUFFER (&parse_in))
-#endif
+      cpp_pop_buffer (parse_in);
+      if (! CPP_BUFFER (parse_in))
        return 0;
       goto retry;
 
@@ -3299,7 +3318,6 @@ _yylex ()
       /* These tokens should not survive translation phase 4.  */
     case CPP_HASH:
     case CPP_PASTE:
-    case CPP_BACKSLASH:
       error ("syntax error before '%s' token", NAME(last_token));
       goto retry;