c-decl.c (c_in_iteration_stmt, [...]): Remove.
authorRichard Henderson <rth@redhat.com>
Thu, 24 Jun 2004 23:12:30 +0000 (16:12 -0700)
committerRichard Henderson <rth@gcc.gnu.org>
Thu, 24 Jun 2004 23:12:30 +0000 (16:12 -0700)
* c-decl.c (c_in_iteration_stmt, c_in_case_stmt): Remove.
(c_break_label, c_cont_label): New.
(start_function): Update initializations.
(c_push_function_context): Update saves.
(c_pop_function_context): Update restores.
* c-parse.in: Update expected conflicts.
(stmt_count, compstmt_count): Remove.  Remove all updates.
(if_prefix, simple_if, do_stmt_start): Remove.
(lineno_labeled_stmt): Remove.
(lineno_labels): New.
(c99_block_lineno_labeled_stmt): Use it.
(lineno_stmt, lineno_label): Don't clear EXPR_LOCUS before calling
annotate_with_locus.
(select_or_iter_stmt): Replace by ...
(condition, if_statement_1, if_statement_2, if_statement,
start_break, start_continue, while_statement, do_statement,
for_cond_expr, for_incr_expr, for_statement, switch_statement): New.
(stmt): Split out ...
(stmt_nocomp): ... this.  Use c_finish_bc_stmt, c_finish_goto_label,
c_finish_goto_ptr.
* c-semantics.c (add_stmt): Don't add line numbers to labels.
* c-tree.h: Update prototypes.
(struct language_function): Remove x_in_iteration_stmt, x_in_case_stmt;
add x_break_label, x_cont_label, x_switch_stack.
(c_switch_stack): Declare.
* c-typeck.c (c_finish_goto_label, c_finish_goto_ptr): New.
(c_finish_return): Return the statement.
(c_switch_stack): Rename from switch_stack; export.
(if_elt, if_stack, if_stack_space, if_stack_pointer): Remove.
(c_begin_if_stmt, c_finish_if_cond, c_finish_then, c_begin_else,
c_finish_else): Remove.
(c_finish_if_stmt): Rewrite to perform the entire operation.
(c_begin_while_stmt, c_finish_while_stmt_cond, c_finish_while_stmt,
c_begin_for_stmt, c_finish_for_stmt_init, c_finish_for_stmt_cond,
c_finish_for_stmt_incr, c_finish_for_stmt): Remove.
(c_finish_loop): New.
(c_finish_bc_stmt): New.
(c_finish_expr_stmt): Return the statement.  Split out...
(c_process_expr_stmt): ... this.  Don't add locus to error marks.
* gimplify.c (gimplify_cond_expr): Accept NULL type statements.
* tree-gimple.c (is_gimple_stmt): Likewise.
* tree-pretty-print.c (dump_generic_node <COND_EXPR>): Likewise.
(print_struct_decl): Delete empty compound statement.
* objc/objc-act.c (objc_build_throw_stmt): Return the statement.
* objc/objc-act.h: Update decl.

From-SVN: r83620

gcc/ChangeLog
gcc/c-decl.c
gcc/c-parse.in
gcc/c-semantics.c
gcc/c-tree.h
gcc/c-typeck.c
gcc/gimplify.c
gcc/objc/objc-act.c
gcc/objc/objc-act.h
gcc/tree-gimple.c
gcc/tree-pretty-print.c

index d46bb0a8f0a42aeae96b0ee0168a1e597654e117..16ad75d409a613bb02fed8ccec656f1681abf34d 100644 (file)
@@ -1,3 +1,51 @@
+2004-06-24  Richard Henderson  <rth@redhat.com>
+
+       * c-decl.c (c_in_iteration_stmt, c_in_case_stmt): Remove.
+       (c_break_label, c_cont_label): New.
+       (start_function): Update initializations.
+       (c_push_function_context): Update saves.
+       (c_pop_function_context): Update restores.
+       * c-parse.in: Update expected conflicts.
+       (stmt_count, compstmt_count): Remove.  Remove all updates.
+       (if_prefix, simple_if, do_stmt_start): Remove.
+       (lineno_labeled_stmt): Remove.
+       (lineno_labels): New.
+       (c99_block_lineno_labeled_stmt): Use it.
+       (lineno_stmt, lineno_label): Don't clear EXPR_LOCUS before calling
+       annotate_with_locus.
+       (select_or_iter_stmt): Replace by ...
+       (condition, if_statement_1, if_statement_2, if_statement,
+       start_break, start_continue, while_statement, do_statement,
+       for_cond_expr, for_incr_expr, for_statement, switch_statement): New.
+       (stmt): Split out ...
+       (stmt_nocomp): ... this.  Use c_finish_bc_stmt, c_finish_goto_label,
+       c_finish_goto_ptr.
+       * c-semantics.c (add_stmt): Don't add line numbers to labels.
+       * c-tree.h: Update prototypes.
+       (struct language_function): Remove x_in_iteration_stmt, x_in_case_stmt;
+       add x_break_label, x_cont_label, x_switch_stack.
+       (c_switch_stack): Declare.
+       * c-typeck.c (c_finish_goto_label, c_finish_goto_ptr): New.
+       (c_finish_return): Return the statement.
+       (c_switch_stack): Rename from switch_stack; export.
+       (if_elt, if_stack, if_stack_space, if_stack_pointer): Remove.
+       (c_begin_if_stmt, c_finish_if_cond, c_finish_then, c_begin_else,
+       c_finish_else): Remove.
+       (c_finish_if_stmt): Rewrite to perform the entire operation.
+       (c_begin_while_stmt, c_finish_while_stmt_cond, c_finish_while_stmt,
+       c_begin_for_stmt, c_finish_for_stmt_init, c_finish_for_stmt_cond,
+       c_finish_for_stmt_incr, c_finish_for_stmt): Remove.
+       (c_finish_loop): New.
+       (c_finish_bc_stmt): New.
+       (c_finish_expr_stmt): Return the statement.  Split out...
+       (c_process_expr_stmt): ... this.  Don't add locus to error marks.
+       * gimplify.c (gimplify_cond_expr): Accept NULL type statements.
+       * tree-gimple.c (is_gimple_stmt): Likewise.
+       * tree-pretty-print.c (dump_generic_node <COND_EXPR>): Likewise.
+       (print_struct_decl): Delete empty compound statement.
+       * objc/objc-act.c (objc_build_throw_stmt): Return the statement.
+       * objc/objc-act.h: Update decl.
+
 2004-06-24  Richard Kenner  <kenner@vlsi1.ultra.nyu.edu>
 
        * tree-pretty-print.c (dump_generic_node, case TYPE_DECL):
index f3170207a0e7ae2b18dcd736cf59aac3744def06..7aeba0896c265d57215493cc3af0ee0c8c36baaa 100644 (file)
@@ -109,8 +109,8 @@ static location_t current_function_prototype_locus;
 static GTY(()) struct stmt_tree_s c_stmt_tree;
 
 /* State saving variables.  */
-int c_in_iteration_stmt;
-int c_in_case_stmt;
+tree c_break_label;
+tree c_cont_label;
 
 /* Linked list of TRANSLATION_UNIT_DECLS for the translation units
    included in this invocation.  Note that the current translation
@@ -5592,8 +5592,12 @@ start_function (tree declspecs, tree declarator, tree attributes)
   current_function_returns_abnormally = 0;
   warn_about_return_type = 0;
   current_extern_inline = 0;
-  c_in_iteration_stmt = 0;
-  c_in_case_stmt = 0;
+  c_switch_stack = NULL;
+
+  /* Indicate no valid break/continue context by setting these variables
+     to some non-null, non-label value.  We'll notice and emit the proper
+     error message in c_finish_bc_stmt.  */
+  c_break_label = c_cont_label = size_zero_node;
 
   /* Don't expand any sizes in the return type of the function.  */
   immediate_size_expand = 0;
@@ -6410,8 +6414,9 @@ c_push_function_context (struct function *f)
   f->language = p;
 
   p->base.x_stmt_tree = c_stmt_tree;
-  p->x_in_iteration_stmt = c_in_iteration_stmt;
-  p->x_in_case_stmt = c_in_case_stmt;
+  p->x_break_label = c_break_label;
+  p->x_cont_label = c_cont_label;
+  p->x_switch_stack = c_switch_stack;
   p->returns_value = current_function_returns_value;
   p->returns_null = current_function_returns_null;
   p->returns_abnormally = current_function_returns_abnormally;
@@ -6437,8 +6442,9 @@ c_pop_function_context (struct function *f)
     }
 
   c_stmt_tree = p->base.x_stmt_tree;
-  c_in_iteration_stmt = p->x_in_iteration_stmt;
-  c_in_case_stmt = p->x_in_case_stmt;
+  c_break_label = p->x_break_label;
+  c_cont_label = p->x_cont_label;
+  c_switch_stack = p->x_switch_stack;
   current_function_returns_value = p->returns_value;
   current_function_returns_null = p->returns_null;
   current_function_returns_abnormally = p->returns_abnormally;
index b7acb71171874efb20cd0d33aca7621b5ab34877..a96241a3e5cc1fe4de1ea7aaa12c347e01146ca4 100644 (file)
@@ -29,7 +29,7 @@ Software Foundation, 59 Temple Place - Suite 330, Boston, MA
    written by AT&T, but I have never seen it.  */
 
 @@ifc
-%expect 10 /* shift/reduce conflicts, and no reduce/reduce conflicts.  */
+%expect 13 /* shift/reduce conflicts, and no reduce/reduce conflicts.  */
 @@end_ifc
 
 %{
@@ -210,9 +210,10 @@ do {                                                                       \
 %type <ttype> any_word
 
 %type <ttype> compstmt compstmt_start compstmt_primary_start
-%type <ttype> do_stmt_start stmt label
+%type <ttype> stmt label stmt_nocomp start_break start_continue
 
 %type <ttype> c99_block_start c99_block_lineno_labeled_stmt
+%type <ttype> if_statement_1 if_statement_2
 %type <ttype> declarator
 %type <ttype> notype_declarator after_type_declarator
 %type <ttype> parm_declarator
@@ -227,7 +228,8 @@ do {                                                                        \
 %type <ttype> struct_head union_head enum_head
 %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> condition xexpr for_cond_expr for_incr_expr
+%type <ttype> parms parm firstparm identifiers
 
 %type <ttype> parmlist parmlist_1 parmlist_2
 %type <ttype> parmlist_or_identifiers parmlist_or_identifiers_1
@@ -254,11 +256,6 @@ do {                                                                       \
 @@end_ifobjc
 \f
 %{
-/* Number of statements (loosely speaking) and compound statements
-   seen so far.  */
-static int stmt_count;
-static int compstmt_count;
-
 /* List of types and structure classes of the current declaration.  */
 static GTY(()) tree current_declspecs;
 static GTY(()) tree prefix_attributes;
@@ -2032,8 +2029,7 @@ compstmt_or_error:
        | error compstmt
        ;
 
-compstmt_start: '{' { compstmt_count++;
-                      $$ = c_begin_compound_stmt (true); }
+compstmt_start: '{' { $$ = c_begin_compound_stmt (true); }
         ;
 
 compstmt_nostart: '}'
@@ -2053,7 +2049,6 @@ compstmt_primary_start:
                             "only inside a function");
                      YYERROR;
                    }
-                 compstmt_count++;
                  $$ = c_begin_stmt_expr ();
                }
         ;
@@ -2062,47 +2057,6 @@ compstmt: compstmt_start compstmt_nostart
                { $$ = c_end_compound_stmt ($1, true); }
        ;
 
-if_prefix:
-         /* We must build the if statement node before parsing its
-            condition so that we get its location pointing to the
-            line containing the "if", and not the line containing
-            the close-parenthesis.  */
-          IF
-                { c_begin_if_stmt (); }
-            '(' expr ')'
-               { c_finish_if_cond ($4, compstmt_count, ++stmt_count); }
-        ;
-
-simple_if:
-         if_prefix c99_block_lineno_labeled_stmt
-                { c_finish_then ($2); }
-       /* Make sure c_finish_if_stmt is run for each call to
-          c_begin_if_stmt.  Otherwise a crash is likely.  */
-       | if_prefix error
-       ;
-
-/* This is a subroutine of stmt.
-   It is used twice, once for valid DO statements
-   and once for catching errors in parsing the end test.  */
-do_stmt_start:
-         DO
-               { stmt_count++;
-                 compstmt_count++;
-                 c_in_iteration_stmt++;
-                 $<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;
-                 DO_BODY ($$) = $3;
-                 c_in_iteration_stmt--; }
-       ;
-
 /* The forced readahead in here is because we might be at the end of a
    line, and the line and file won't be bumped until yylex absorbs the
    first token on the next line.  */
@@ -2113,14 +2067,14 @@ save_location:
                  $$ = input_location; }
        ;
 
-lineno_labeled_stmt:
-         lineno_stmt
-       | lineno_label lineno_labeled_stmt
+lineno_labels:
+         /* empty */
+       | lineno_labels lineno_label
        ;
 
-/* Like lineno_labeled_stmt, but a block in C99.  */
+/* A labeled statement.  In C99 it also generates an implicit block.  */
 c99_block_lineno_labeled_stmt:
-         c99_block_start lineno_labeled_stmt
+         c99_block_start lineno_labels lineno_stmt
                 { $$ = c_end_compound_stmt ($1, flag_isoc99); }
        ;
 
@@ -2138,74 +2092,91 @@ lineno_stmt:
                     because (recursively) all of the component statments
                     should already have line numbers assigned.  */
                  if ($2 && EXPR_P ($2))
-                   {
-                     SET_EXPR_LOCUS ($2, NULL);
-                     annotate_with_locus ($2, $1);
-                   }
+                   annotate_with_locus ($2, $1);
                }
        ;
 
 lineno_label:
          save_location label
-               { if ($2)
-                   {
-                     SET_EXPR_LOCUS ($2, NULL);
-                     annotate_with_locus ($2, $1);
-                   }
-               }
+               { if ($2) annotate_with_locus ($2, $1); }
        ;
 
-select_or_iter_stmt:
-         simple_if ELSE
-               { c_begin_else (stmt_count); }
-         c99_block_lineno_labeled_stmt
-                { c_finish_else ($4); c_finish_if_stmt (stmt_count); }
-       | simple_if %prec IF
-               { c_finish_if_stmt (stmt_count); }
-       | simple_if ELSE error
-               { c_finish_if_stmt (stmt_count + 1); }
-       /* We must build the WHILE_STMT node before parsing its
-         condition so that EXPR_LOCUS 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++;
-                 $<ttype>$ = c_begin_while_stmt (); }
-         '(' expr ')'
-                { c_in_iteration_stmt++;
-                 c_finish_while_stmt_cond ($4, $<ttype>2); }
-         c99_block_lineno_labeled_stmt
-                { c_in_iteration_stmt--;
-                 c_finish_while_stmt ($7, $<ttype>2); }
-       | do_stmt_start
-         '(' expr ')' ';'
-                { DO_COND ($1) = lang_hooks.truthvalue_conversion ($3); }
-       | do_stmt_start error
-               { }
-       | FOR
-               { $<ttype>$ = c_begin_for_stmt (); }
-         '(' for_init_stmt
-               { stmt_count++;
-                 c_finish_for_stmt_init ($<ttype>2); }
-         xexpr ';'
-                { c_finish_for_stmt_cond ($6, $<ttype>2); }
-         xexpr ')'
-                { c_in_iteration_stmt++;
-                 c_finish_for_stmt_incr ($9, $<ttype>2); }
-         c99_block_lineno_labeled_stmt
-                { c_finish_for_stmt ($12, $<ttype>2);
-                 c_in_iteration_stmt--; }
-       | SWITCH '(' expr ')'
-               { stmt_count++;
-                 $<ttype>$ = c_start_case ($3);
-                 c_in_case_stmt++; }
-         c99_block_lineno_labeled_stmt
-                { c_finish_case ($6);
-                 c_in_case_stmt--; }
+condition: save_location expr
+               { $$ = lang_hooks.truthvalue_conversion ($2);
+                 if (EXPR_P ($$))
+                   annotate_with_locus ($$, $1); }
+       ;
+
+/* Implement -Wparenthesis by special casing IF statement directly nested
+   within IF statement.  This requires some amount of duplication of the
+   productions under c99_block_lineno_labeled_stmt in order to work out.
+   But it's still likely more maintainable than lots of state outside the
+   parser...  */
+
+if_statement_1:
+       c99_block_start lineno_labels if_statement
+               { $$ = c_end_compound_stmt ($1, flag_isoc99); }
+       ;
+
+if_statement_2:
+         c99_block_start lineno_labels ';'
+               { if (extra_warnings)
+                   add_stmt (build (NOP_EXPR, NULL_TREE, NULL_TREE));
+                 $$ = c_end_compound_stmt ($1, flag_isoc99); }
+       | c99_block_lineno_labeled_stmt
+       ;
+
+if_statement:
+         IF c99_block_start save_location '(' condition ')'
+           if_statement_1 ELSE if_statement_2
+               { c_finish_if_stmt ($3, $5, $7, $9, true);
+                 add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
+       | IF c99_block_start save_location '(' condition ')'
+           if_statement_2 ELSE if_statement_2
+               { c_finish_if_stmt ($3, $5, $7, $9, false);
+                 add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
+       | IF c99_block_start save_location '(' condition ')'
+           if_statement_1                              %prec IF
+               { c_finish_if_stmt ($3, $5, $7, NULL, true);
+                 add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
+       | IF c99_block_start save_location '(' condition ')'
+           if_statement_2                              %prec IF
+               { c_finish_if_stmt ($3, $5, $7, NULL, false);
+                 add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
+       ;
+
+start_break: /* empty */
+               { $$ = c_break_label; c_break_label = NULL; }
+       ;
+
+start_continue: /* empty */
+               { $$ = c_cont_label; c_cont_label = NULL; }
+       ;
+
+while_statement:
+       WHILE c99_block_start save_location '(' condition ')'
+       start_break start_continue c99_block_lineno_labeled_stmt
+               { c_finish_loop ($3, $5, NULL, $9, c_break_label,
+                                c_cont_label, true);
+                 add_stmt (c_end_compound_stmt ($2, flag_isoc99));
+                 c_break_label = $7; c_cont_label = $8; }
+       ;
+
+do_statement:
+       DO c99_block_start save_location start_break start_continue
+       c99_block_lineno_labeled_stmt WHILE
+               { $<ttype>$ = c_break_label; c_break_label = $4; }
+               { $<ttype>$ = c_cont_label; c_cont_label = $5; }
+       '(' condition ')' ';'
+                { c_finish_loop ($3, $11, NULL, $6, $<ttype>8,
+                                $<ttype>9, false);
+                 add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
+       ;
+
+xexpr:
+       /* empty */
+               { $$ = NULL_TREE; }
+       | expr
        ;
 
 for_init_stmt:
@@ -2215,64 +2186,82 @@ for_init_stmt:
                { check_for_loop_decls (); }
        ;
 
-xexpr:
-       /* empty */
-               { $$ = NULL_TREE; }
-       | expr
+for_cond_expr: save_location xexpr
+               { if ($2)
+                   {
+                     $$ = lang_hooks.truthvalue_conversion ($2);
+                     if (EXPR_P ($$))
+                       annotate_with_locus ($$, $1);
+                   }
+                 else
+                   $$ = NULL;
+               }
        ;
 
-/* Parse a single real statement, not including any labels.  */
-stmt:
-         compstmt
-               { stmt_count++; add_stmt ($1); }
-       | expr ';'
-               { stmt_count++; c_finish_expr_stmt ($1); }
-       | c99_block_start select_or_iter_stmt
-                { add_stmt (c_end_compound_stmt ($1, flag_isoc99)); }
+for_incr_expr: xexpr
+               { $$ = c_process_expr_stmt ($1); }
+       ;
+
+for_statement:
+       FOR c99_block_start '(' for_init_stmt
+       save_location for_cond_expr ';' for_incr_expr ')'
+       start_break start_continue c99_block_lineno_labeled_stmt
+               { c_finish_loop ($5, $6, $8, $12, c_break_label,
+                                c_cont_label, true);
+                 add_stmt (c_end_compound_stmt ($2, flag_isoc99));
+                 c_break_label = $10; c_cont_label = $11; }
+       ;
+
+switch_statement:
+       SWITCH c99_block_start '(' expr ')'
+               { $<ttype>$ = c_start_case ($4); }
+       start_break c99_block_lineno_labeled_stmt
+                { c_finish_case ($8);
+                 if (c_break_label)
+                   add_stmt (build (LABEL_EXPR, void_type_node,
+                                    c_break_label));
+                 c_break_label = $7;
+                 add_stmt (c_end_compound_stmt ($2, flag_isoc99)); }
+       ;
+
+/* Parse a single real statement, not including any labels or compounds.  */
+stmt_nocomp:
+         expr ';'
+               { $$ = c_finish_expr_stmt ($1); }
+       | if_statement
+               { $$ = NULL_TREE; }
+       | while_statement
+               { $$ = NULL_TREE; }
+       | do_statement
+               { $$ = NULL_TREE; }
+       | for_statement
+               { $$ = NULL_TREE; }
+       | switch_statement
+               { $$ = NULL_TREE; }
        | BREAK ';'
-               { stmt_count++;
-                 if (!(c_in_iteration_stmt || c_in_case_stmt))
-                   error ("break statement not within loop or switch");
-                 else
-                   add_stmt (build_break_stmt ()); }
+               { $$ = c_finish_bc_stmt (&c_break_label, true); }
        | CONTINUE ';'
-                { stmt_count++;
-                 if (!c_in_iteration_stmt)
-                   error ("continue statement not within a loop");
-                 else
-                   add_stmt (build_continue_stmt ()); }
+                { $$ = c_finish_bc_stmt (&c_cont_label, false); }
        | RETURN ';'
-                { stmt_count++; c_finish_return (NULL_TREE); }
+                { $$ = c_finish_return (NULL_TREE); }
        | RETURN expr ';'
-                { stmt_count++; c_finish_return ($2); }
+                { $$ = c_finish_return ($2); }
        | asm_stmt
        | GOTO identifier ';'
-               { tree decl;
-                 stmt_count++;
-                 decl = lookup_label ($2);
-                 if (decl != 0)
-                   {
-                     TREE_USED (decl) = 1;
-                     add_stmt (build_stmt (GOTO_EXPR, decl));
-                   }
-               }
+               { $$ = c_finish_goto_label ($2); }
        | GOTO '*' expr ';'
-               { if (pedantic)
-                   pedwarn ("ISO C forbids `goto *expr;'");
-                 stmt_count++;
-                 $3 = convert (ptr_type_node, $3);
-                 add_stmt (build_stmt (GOTO_EXPR, $3)); }
+               { $$ = c_finish_goto_ptr ($3); }
        | ';'
-               { }
+               { $$ = NULL_TREE; }
 @@ifobjc
        | AT_THROW expr ';'
-               { stmt_count++; objc_build_throw_stmt ($2); }
+               { $$ = objc_build_throw_stmt ($2); }
        | AT_THROW ';'
-               { stmt_count++; objc_build_throw_stmt (NULL_TREE); }
+               { $$ = objc_build_throw_stmt (NULL_TREE); }
        | objc_try_catch_stmt
-               { }
-       | AT_SYNCHRONIZED '(' expr ')' save_location compstmt
-               { stmt_count++; objc_build_synchronized ($5, $3, $6); }
+               { $$ = NULL_TREE; }
+       | AT_SYNCHRONIZED save_location '(' expr ')' compstmt
+               { objc_build_synchronized ($2, $4, $6); $$ = NULL_TREE; }
        ;
 
 objc_catch_prefix:
@@ -2294,7 +2283,7 @@ objc_opt_catch_list:
 
 objc_try_catch_clause:
        AT_TRY save_location compstmt
-               { stmt_count++; objc_begin_try_stmt ($2, $3); }
+               { objc_begin_try_stmt ($2, $3); }
        objc_opt_catch_list
        ;
 
@@ -2311,22 +2300,25 @@ objc_try_catch_stmt:
 @@end_ifobjc
        ;
 
+/* Parse a single or compound real statement, not including any labels.  */
+stmt:
+         compstmt
+               { add_stmt ($1); $$ = NULL_TREE; }
+       | stmt_nocomp
+       ;
+
 /* Any kind of label, including jump labels and case labels.
    ANSI C accepts labels only before statements, but we allow them
    also at the end of a compound statement.  */
 
 label:   CASE expr_no_commas ':'
-                { stmt_count++;
-                 $$ = do_case ($2, NULL_TREE); }
+                { $$ = do_case ($2, NULL_TREE); }
        | CASE expr_no_commas ELLIPSIS expr_no_commas ':'
-                { stmt_count++;
-                 $$ = do_case ($2, $4); }
+                { $$ = do_case ($2, $4); }
        | DEFAULT ':'
-                { stmt_count++;
-                 $$ = do_case (NULL_TREE, NULL_TREE); }
+                { $$ = do_case (NULL_TREE, NULL_TREE); }
        | identifier save_location ':' maybe_attribute
                { tree label = define_label ($2, $1);
-                 stmt_count++;
                  if (label)
                    {
                      decl_attributes (&label, $4, 0);
@@ -2367,8 +2359,7 @@ asmdef:
 asm_stmt:
        ASM_KEYWORD maybe_volatile stop_string_translation
                '(' asm_argument ')' start_string_translation ';'
-               { stmt_count++;
-                 $$ = build_asm_stmt ($2, $5); }
+               { $$ = build_asm_stmt ($2, $5); }
        ;
 
 asm_argument:
index ee04417ad08bb55fc6db08f54725747d634cefc2..9512947216cfc3482d9c6698fb47c142be3d11ee 100644 (file)
@@ -128,7 +128,9 @@ pop_stmt_list (tree t)
 tree
 add_stmt (tree t)
 {
-  if (EXPR_P (t) || STATEMENT_CODE_P (TREE_CODE (t)))
+  enum tree_code code = TREE_CODE (t);
+
+  if ((EXPR_P (t) || STATEMENT_CODE_P (code)) && code != LABEL_EXPR)
     {
       if (!EXPR_LOCUS (t))
        annotate_with_locus (t, input_location);
index 66691eba29999325321a46091fa9f4abd26115d9..4d99c409f3bca3ecc875d2e8c2e0ec5509deb4dc 100644 (file)
@@ -126,13 +126,14 @@ struct lang_type GTY(())
 struct language_function GTY(())
 {
   struct c_language_function base;
+  tree x_break_label;
+  tree x_cont_label;
+  struct c_switch * GTY((skip)) x_switch_stack;
   int returns_value;
   int returns_null;
   int returns_abnormally;
   int warn_about_return_type;
   int extern_inline;
-  int x_in_iteration_stmt;
-  int x_in_case_stmt;
 };
 
 \f
@@ -143,8 +144,8 @@ extern void c_parse_init (void);
 extern void gen_aux_info_record (tree, int, int, int);
 
 /* in c-decl.c */
-extern int c_in_iteration_stmt;
-extern int c_in_case_stmt;
+extern tree c_break_label;
+extern tree c_cont_label;
 
 extern int global_bindings_p (void);
 extern void push_scope (void);
@@ -212,6 +213,7 @@ extern bool c_warn_unused_global_decl (tree);
 #define c_sizeof_nowarn(T)  c_sizeof_or_alignof_type (T, SIZEOF_EXPR, 0)
 
 /* in c-typeck.c */
+extern struct c_switch *c_switch_stack;
 
 extern tree require_complete_type (tree);
 extern int same_translation_unit_p (tree, tree);
@@ -254,24 +256,16 @@ extern tree c_convert_parm_for_inlining (tree, tree, tree, int);
 extern int c_types_compatible_p (tree, tree);
 extern tree c_begin_compound_stmt (bool);
 extern tree c_end_compound_stmt (tree, bool);
-extern void c_begin_if_stmt (void);
-extern void c_finish_if_cond (tree, int, int);
-extern void c_finish_then (tree);
-extern void c_begin_else (int);
-extern void c_finish_else (tree);
-extern void c_finish_if_stmt (int);
-extern tree c_begin_while_stmt (void);
-extern void c_finish_while_stmt_cond (tree, tree);
-extern void c_finish_while_stmt (tree, tree);
-extern tree c_begin_for_stmt (void);
-extern void c_finish_for_stmt_init (tree);
-extern void c_finish_for_stmt_cond (tree, tree);
-extern void c_finish_for_stmt_incr (tree, tree);
-extern void c_finish_for_stmt (tree, tree);
+extern void c_finish_if_stmt (location_t, tree, tree, tree, bool);
+extern void c_finish_loop (location_t, tree, tree, tree, tree, tree, bool);
 extern tree c_begin_stmt_expr (void);
 extern tree c_finish_stmt_expr (tree);
-extern void c_finish_expr_stmt (tree);
-extern void c_finish_return (tree);
+extern tree c_process_expr_stmt (tree);
+extern tree c_finish_expr_stmt (tree);
+extern tree c_finish_return (tree);
+extern tree c_finish_bc_stmt (tree *, bool);
+extern tree c_finish_goto_label (tree);
+extern tree c_finish_goto_ptr (tree);
 extern tree build_offsetof (tree, tree);
 
 /* Set to 0 at beginning of a function definition, set to 1 if
index 8a5d06f5761fbd22b8b0ab5ceb7e9522ab2be915..ededd617a23ad49cac95e59ee1edc6fe6c1d91da 100644 (file)
@@ -6249,10 +6249,34 @@ c_expand_asm_operands (tree string, tree outputs, tree inputs,
   emit_queue ();
 }
 \f
+/* Generate a goto statement to LABEL.  */
+
+tree
+c_finish_goto_label (tree label)
+{
+  tree decl = lookup_label (label);
+  if (!decl)
+    return NULL_TREE;
+
+  TREE_USED (decl) = 1;
+  return add_stmt (build (GOTO_EXPR, void_type_node, decl));
+}
+
+/* Generate a computed goto statement to EXPR.  */
+
+tree
+c_finish_goto_ptr (tree expr)
+{
+  if (pedantic)
+    pedwarn ("ISO C forbids `goto *expr;'");
+  expr = convert (ptr_type_node, expr);
+  return add_stmt (build (GOTO_EXPR, void_type_node, expr));
+}
+
 /* Generate a C `return' statement.  RETVAL is the expression for what
    to return, or a null pointer for `return;' with no value.  */
 
-void
+tree
 c_finish_return (tree retval)
 {
   tree valtype = TREE_TYPE (TREE_TYPE (current_function_decl));
@@ -6282,7 +6306,7 @@ c_finish_return (tree retval)
 
       current_function_returns_value = 1;
       if (t == error_mark_node)
-       return;
+       return NULL_TREE;
 
       inner = t = convert (TREE_TYPE (res), t);
 
@@ -6340,7 +6364,7 @@ c_finish_return (tree retval)
       retval = build (MODIFY_EXPR, TREE_TYPE (res), res, t);
     }
 
-  add_stmt (build_stmt (RETURN_EXPR, retval));
+  return add_stmt (build_stmt (RETURN_EXPR, retval));
 }
 \f
 struct c_switch {
@@ -6362,7 +6386,7 @@ struct c_switch {
    during the processing of the body of a function, and we never
    collect at that point.  */
 
-static struct c_switch *switch_stack;
+struct c_switch *c_switch_stack;
 
 /* Start a C switch statement, testing expression EXP.  Return the new
    SWITCH_STMT.  */
@@ -6403,10 +6427,10 @@ c_start_case (tree exp)
   cs = xmalloc (sizeof (*cs));
   cs->switch_stmt = build_stmt (SWITCH_STMT, exp, NULL_TREE, orig_type);
   cs->cases = splay_tree_new (case_compare, NULL, NULL);
-  cs->next = switch_stack;
-  switch_stack = cs;
+  cs->next = c_switch_stack;
+  c_switch_stack = cs;
 
-  return add_stmt (switch_stack->switch_stmt);
+  return add_stmt (cs->switch_stmt);
 }
 
 /* Process a case label.  */
@@ -6416,10 +6440,10 @@ do_case (tree low_value, tree high_value)
 {
   tree label = NULL_TREE;
 
-  if (switch_stack)
+  if (c_switch_stack)
     {
-      label = c_add_case_label (switch_stack->cases,
-                               SWITCH_COND (switch_stack->switch_stmt),
+      label = c_add_case_label (c_switch_stack->cases,
+                               SWITCH_COND (c_switch_stack->switch_stmt),
                                low_value, high_value);
       if (label == error_mark_node)
        label = NULL_TREE;
@@ -6437,7 +6461,7 @@ do_case (tree low_value, tree high_value)
 void
 c_finish_case (tree body)
 {
-  struct c_switch *cs = switch_stack;
+  struct c_switch *cs = c_switch_stack;
 
   SWITCH_BODY (cs->switch_stmt) = body;
 
@@ -6445,206 +6469,171 @@ c_finish_case (tree body)
   c_do_switch_warnings (cs->cases, cs->switch_stmt);
 
   /* Pop the stack.  */
-  switch_stack = switch_stack->next;
+  c_switch_stack = cs->next;
   splay_tree_delete (cs->cases);
   free (cs);
 }
 \f
-/* Keep a stack of if statements.  We record the number of compound
-   statements seen up to the if keyword, as well as the line number
-   and file of the if.  If a potentially ambiguous else is seen, that
-   fact is recorded; the warning is issued when we can be sure that
-   the enclosing if statement does not have an else branch.  */
-typedef struct
-{
-  tree if_stmt;
-  location_t empty_locus;
-  int compstmt_count;
-  int stmt_count;
-  unsigned int needs_warning : 1;
-  unsigned int saw_else : 1;
-} if_elt;
-
-static if_elt *if_stack;
-
-/* Amount of space in the if statement stack.  */
-static int if_stack_space = 0;
-
-/* Stack pointer.  */
-static int if_stack_pointer = 0;
-
-/* Begin an if-statement.  */
+/* Emit an if statement.  IF_LOCUS is the location of the 'if'.  COND,
+   THEN_BLOCK and ELSE_BLOCK are expressions to be used; ELSE_BLOCK
+   may be null.  NESTED_IF is true if THEN_BLOCK contains another IF
+   statement, and was not surrounded with parenthesis.  */
 
 void
-c_begin_if_stmt (void)
+c_finish_if_stmt (location_t if_locus, tree cond, tree then_block,
+                 tree else_block, bool nested_if)
 {
-  tree r;
-  if_elt *elt;
+  tree stmt;
 
-  /* Make sure there is enough space on the stack.  */
-  if (if_stack_space == 0)
+  /* Diagnose an ambiguous else if if-then-else is nested inside if-then.  */
+  if (warn_parentheses && nested_if && else_block == NULL)
     {
-      if_stack_space = 10;
-      if_stack = xmalloc (10 * sizeof (if_elt));
-    }
-  else if (if_stack_space == if_stack_pointer)
-    {
-      if_stack_space += 10;
-      if_stack = xrealloc (if_stack, if_stack_space * sizeof (if_elt));
-    }
-
-  r = add_stmt (build_stmt (COND_EXPR, NULL_TREE, NULL_TREE, NULL_TREE));
-
-  /* Record this if statement.  */
-  elt = &if_stack[if_stack_pointer++];
-  memset (elt, 0, sizeof (*elt));
-  elt->if_stmt = r;
-}
-
-/* Record the start of an if-then, and record the start of it
-   for ambiguous else detection.
+      tree inner_if = then_block;
 
-   COND is the condition for the if-then statement.
-
-   IF_STMT is the statement node that has already been created for
-   this if-then statement.  It is created before parsing the
-   condition to keep line number information accurate.  */
-
-void
-c_finish_if_cond (tree cond, int compstmt_count, int stmt_count)
-{
-  if_elt *elt = &if_stack[if_stack_pointer - 1];
-  elt->compstmt_count = compstmt_count;
-  elt->stmt_count = stmt_count;
-  COND_EXPR_COND (elt->if_stmt) = lang_hooks.truthvalue_conversion (cond);
-}
-
-/* Called after the then-clause for an if-statement is processed.  */
-
-void
-c_finish_then (tree then_stmt)
-{
-  if_elt *elt = &if_stack[if_stack_pointer - 1];
-  COND_EXPR_THEN (elt->if_stmt) = then_stmt;
-  elt->empty_locus = input_location;
-}
-
-/* Called between the then-clause and the else-clause
-   of an if-then-else.  */
-
-void
-c_begin_else (int stmt_count)
-{
-  if_elt *elt = &if_stack[if_stack_pointer - 1];
-
-  /* An ambiguous else warning must be generated for the enclosing if
-     statement, unless we see an else branch for that one, too.  */
-  if (warn_parentheses
-      && if_stack_pointer > 1
-      && (elt[0].compstmt_count == elt[-1].compstmt_count))
-    elt[-1].needs_warning = 1;
-
-  /* Even if a nested if statement had an else branch, it can't be
-     ambiguous if this one also has an else.  So don't warn in that
-     case.  Also don't warn for any if statements nested in this else.  */
-  elt->needs_warning = 0;
-  elt->compstmt_count--;
-  elt->saw_else = 1;
-  elt->stmt_count = stmt_count;
-}
-
-/* Called after the else-clause for an if-statement is processed.  */
-
-void
-c_finish_else (tree else_stmt)
-{
-  if_elt *elt = &if_stack[if_stack_pointer - 1];
-  COND_EXPR_ELSE (elt->if_stmt) = else_stmt;
-  elt->empty_locus = input_location;
-}
-
-/* Record the end of an if-then.  Optionally warn if a nested
-   if statement had an ambiguous else clause.  */
-
-void
-c_finish_if_stmt (int stmt_count)
-{
-  if_elt *elt = &if_stack[--if_stack_pointer];
+      /* We know from the grammer productions that there is an IF nested
+        within THEN_BLOCK.  Due to labels and c99 conditional declarations,
+        it might not be exactly THEN_BLOCK, but should be the last
+        non-container statement within.  */
+      while (1)
+       switch (TREE_CODE (inner_if))
+         {
+         case COND_EXPR:
+           goto found;
+         case BIND_EXPR:
+           inner_if = BIND_EXPR_BODY (inner_if);
+           break;
+         case STATEMENT_LIST:
+           inner_if = expr_last (then_block);
+           break;
+         case TRY_FINALLY_EXPR:
+         case TRY_CATCH_EXPR:
+           inner_if = TREE_OPERAND (inner_if, 0);
+           break;
+         default:
+           abort ();
+         }
+    found:
 
-  if (elt->needs_warning)
-    warning ("%Hsuggest explicit braces to avoid ambiguous `else'",
-            EXPR_LOCUS (elt->if_stmt));
+      if (COND_EXPR_ELSE (inner_if))
+        warning ("%Hsuggest explicit braces to avoid ambiguous `else'",
+                 &if_locus);
+    }
 
-  if (extra_warnings && stmt_count == elt->stmt_count)
+  /* Diagnose ";" via the special empty statement node that we create.  */
+  if (extra_warnings)
     {
-      if (elt->saw_else)
-       warning ("%Hempty body in an else-statement", &elt->empty_locus);
-      else
-       warning ("%Hempty body in an if-statement", &elt->empty_locus);
+      if (TREE_CODE (then_block) == NOP_EXPR && !TREE_TYPE (then_block))
+       {
+         if (!else_block)
+           warning ("%Hempty body in an if-statement",
+                    EXPR_LOCUS (then_block));
+         then_block = alloc_stmt_list ();
+       }
+      if (else_block
+         && TREE_CODE (else_block) == NOP_EXPR
+         && !TREE_TYPE (else_block))
+       {
+         warning ("%Hempty body in an else-statement",
+                  EXPR_LOCUS (else_block));
+         else_block = alloc_stmt_list ();
+       }
     }
-}
-\f
-/* Begin a while statement.  Returns a newly created WHILE_STMT if
-   appropriate.  */
 
-tree
-c_begin_while_stmt (void)
-{
-  tree r;
-  r = add_stmt (build_stmt (WHILE_STMT, NULL_TREE, NULL_TREE));
-  return r;
+  stmt = build3 (COND_EXPR, NULL_TREE, cond, then_block, else_block);
+  annotate_with_locus (stmt, if_locus);
+  add_stmt (stmt);
 }
 
-void
-c_finish_while_stmt_cond (tree cond, tree while_stmt)
-{
-  WHILE_COND (while_stmt) = (*lang_hooks.truthvalue_conversion) (cond);
-}
+/* Emit a general-purpose loop construct.  START_LOCUS is the location of
+   the beginning of the loop.  COND is the loop condition.  COND_IS_FIRST
+   is false for DO loops.  INCR is the FOR increment expression.  BODY is
+   the statement controled by the loop.  BLAB is the break label.  CLAB is
+   the continue label.  Everything is allowed to be NULL.  */
 
 void
-c_finish_while_stmt (tree body, tree while_stmt)
+c_finish_loop (location_t start_locus, tree cond, tree incr, tree body,
+              tree blab, tree clab, bool cond_is_first)
 {
-  WHILE_BODY (while_stmt) = body;
+  tree entry = NULL, exit = NULL, t;
+
+  /* Force zeros to NULL so that we don't test them.  */
+  if (cond && integer_zerop (cond))
+    cond = NULL;
+
+  /* Detect do { ... } while (0) and don't generate loop construct.  */
+  if (cond_is_first || cond)
+    {
+      tree top = build1 (LABEL_EXPR, void_type_node, NULL_TREE);
+      /* If we have an exit condition, then we build an IF with gotos either
+         out of the loop, or to the top of it.  If there's no exit condition,
+         then we just build a jump back to the top.  */
+      exit = build_and_jump (&LABEL_EXPR_LABEL (top));
+      if (cond)
+        {
+          /* Canonicalize the loop condition to the end.  This means
+             generating a branch to the loop condition.  Reuse the
+             continue label, if possible.  */
+          if (cond_is_first)
+            {
+              if (incr || !clab)
+                {
+                  entry = build1 (LABEL_EXPR, void_type_node, NULL_TREE);
+                  t = build_and_jump (&LABEL_EXPR_LABEL (entry));
+                }
+              else
+                t = build1 (GOTO_EXPR, void_type_node, clab);
+             annotate_with_locus (t, start_locus);
+              add_stmt (t);
+            }
+         t = build_and_jump (&blab);
+          exit = build (COND_EXPR, void_type_node, cond, exit, t);
+          exit = fold (exit);
+         if (cond_is_first)
+            annotate_with_locus (exit, start_locus);
+         else
+            annotate_with_locus (exit, input_location);
+        }
+      add_stmt (top);
+    }
+  if (body)
+    add_stmt (body);
+  if (clab)
+    add_stmt (build1 (LABEL_EXPR, void_type_node, clab));
+  if (incr)
+    add_stmt (incr);
+  if (entry)
+    add_stmt (entry);
+  if (exit)
+    add_stmt (exit);
+  if (blab)
+    add_stmt (build1 (LABEL_EXPR, void_type_node, blab));
 }
-\f
-/* Create a for statement.  */
 
 tree
-c_begin_for_stmt (void)
+c_finish_bc_stmt (tree *label_p, bool is_break)
 {
-  tree r;
-  r = add_stmt (build_stmt (FOR_STMT, NULL_TREE, NULL_TREE,
-                           NULL_TREE, NULL_TREE));
-  FOR_INIT_STMT (r) = push_stmt_list ();
-  return r;
-}
-
-void
-c_finish_for_stmt_init (tree for_stmt)
-{
-  FOR_INIT_STMT (for_stmt) = pop_stmt_list (FOR_INIT_STMT (for_stmt));
-}
+  tree label = *label_p;
 
-void
-c_finish_for_stmt_cond (tree cond, tree for_stmt)
-{
-  if (cond)
-    FOR_COND (for_stmt) = lang_hooks.truthvalue_conversion (cond);
-}
+  if (!label)
+    *label_p = label = create_artificial_label ();
+  else if (TREE_CODE (label) != LABEL_DECL)
+    {
+      if (is_break)
+       error ("break statement not within loop or switch");
+      else
+        error ("continue statement not within a loop");
+      return NULL_TREE;
+    }
 
-void
-c_finish_for_stmt_incr (tree expr, tree for_stmt)
-{
-  FOR_EXPR (for_stmt) = expr;
+  return add_stmt (build (GOTO_EXPR, void_type_node, label));
 }
 
-void
-c_finish_for_stmt (tree body, tree for_stmt)
-{
-  FOR_BODY (for_stmt) = body;
-}
-\f
-/* A helper routine for c_finish_expr_stmt and c_finish_stmt_expr.  */
+/* A helper routine for c_process_expr_stmt and c_finish_stmt_expr.  */
 
 static void
 emit_side_effect_warnings (tree expr)
@@ -6661,13 +6650,14 @@ emit_side_effect_warnings (tree expr)
     warn_if_unused_value (expr, input_location);
 }
 
-/* Emit an expression as a statement.  */
+/* Process an expression as if it were a complete statement.  Emit
+   diagnostics, but do not call ADD_STMT.  */
 
-void
-c_finish_expr_stmt (tree expr)
+tree
+c_process_expr_stmt (tree expr)
 {
   if (!expr)
-    return;
+    return NULL_TREE;
 
   /* Do default conversion if safe and possibly important,
      in case within ({...}).  */
@@ -6696,7 +6686,21 @@ c_finish_expr_stmt (tree expr)
   if (DECL_P (expr) || TREE_CODE_CLASS (TREE_CODE (expr)) == 'c')
     expr = build1 (NOP_EXPR, TREE_TYPE (expr), expr);
 
-  add_stmt (expr);
+  if (EXPR_P (expr))
+    annotate_with_locus (expr, input_location);
+
+  return expr;
+}
+
+/* Emit an expression as a statement.  */
+
+tree
+c_finish_expr_stmt (tree expr)
+{
+  if (expr)
+    return add_stmt (c_process_expr_stmt (expr));
+  else
+    return NULL;
 }
 
 /* Do the opposite and emit a statement as an expression.  To begin,
index 308f3e9b6a2ff31eabea90ea502e54b731276eb2..a050b2080c342c27df2a384c86de5a540c2adb13 100644 (file)
@@ -2511,12 +2511,16 @@ static enum gimplify_status
 gimplify_cond_expr (tree *expr_p, tree *pre_p, tree target)
 {
   tree expr = *expr_p;
-  tree tmp;
+  tree tmp, type;
   enum gimplify_status ret;
 
+  type = TREE_TYPE (expr);
+  if (!type)
+    TREE_TYPE (expr) = void_type_node;
+
   /* If this COND_EXPR has a value, copy the values into a temporary within
      the arms.  */
-  if (! VOID_TYPE_P (TREE_TYPE (expr)))
+  else if (! VOID_TYPE_P (type))
     {
       if (target)
        {
index 39e6f765ae7a3cefb7dafd6e21294217e8525a62..2ecd03000f4239714a59e146bad7c1ab7a8324ec 100644 (file)
@@ -3188,10 +3188,12 @@ objc_finish_try_stmt (void)
   free (c);
 }
 
-void
+tree
 objc_build_throw_stmt (tree throw_expr)
 {
-  tree func_params;
+  tree args;
+
+  objc_init_exceptions ();
 
   if (throw_expr == NULL)
     {
@@ -3201,7 +3203,7 @@ objc_build_throw_stmt (tree throw_expr)
           || cur_try_context->current_catch == NULL)
        {
          error ("%<@throw%> (rethrow) used outside of a @catch block");
-         return;
+         return NULL_TREE;
        }
 
       /* Otherwise the object is still sitting in the EXC_PTR_EXPR
@@ -3211,10 +3213,8 @@ objc_build_throw_stmt (tree throw_expr)
 
   /* A throw is just a call to the runtime throw function with the
      object as a parameter.  */
-  func_params = tree_cons (NULL, throw_expr, NULL);
-  add_stmt (build_function_call (objc_exception_throw_decl, func_params));
-
-  objc_init_exceptions ();
+  args = tree_cons (NULL, throw_expr, NULL);
+  return add_stmt (build_function_call (objc_exception_throw_decl, args));
 }
 
 void
index ab2ea08fd1e2d91e912e0d2074a01657fa0d767f..2472bfe711fc4106b4a296bc75b137e0f84ddaa1 100644 (file)
@@ -39,7 +39,7 @@ void finish_method_def (void);
 tree start_protocol (enum tree_code, tree, tree);
 void finish_protocol (tree);
 
-void objc_build_throw_stmt (tree);
+tree objc_build_throw_stmt (tree);
 void objc_begin_try_stmt (location_t, tree);
 void objc_begin_catch_clause (tree);
 void objc_finish_catch_clause (void);
index 2deee183964398d9f7c02c13dc1a6a4a7227c00b..f90e9acc488f4ccaeab8d13df0166b349a4759be 100644 (file)
@@ -348,7 +348,7 @@ is_gimple_stmt (tree t)
     case BIND_EXPR:
     case COND_EXPR:
       /* These are only valid if they're void.  */
-      return VOID_TYPE_P (TREE_TYPE (t));
+      return TREE_TYPE (t) == NULL || VOID_TYPE_P (TREE_TYPE (t));
 
     case SWITCH_EXPR:
     case GOTO_EXPR:
index 477c2830b32acc6867efdcff62adcf8fbc7c8321..5fe5a4f677a0af575877f748dccffbb6c5b29c88 100644 (file)
@@ -767,7 +767,7 @@ dump_generic_node (pretty_printer *buffer, tree node, int spc, int flags,
       break;
 
     case COND_EXPR:
-      if (TREE_TYPE (node) == void_type_node)
+      if (TREE_TYPE (node) == NULL || TREE_TYPE (node) == void_type_node)
        {
          pp_string (buffer, "if (");
          dump_generic_node (buffer, COND_EXPR_COND (node), spc, flags, false);
@@ -1543,10 +1543,6 @@ print_struct_decl (pretty_printer *buffer, tree node, int spc, int flags)
            print_declaration (buffer, tmp, spc+2, flags);
            pp_newline (buffer);
          }
-       else
-         {
-
-         }
        tmp = TREE_CHAIN (tmp);
       }
   }