diff --git a/gcc/ChangeLog b/gcc/ChangeLog index edb9596c56ed98ef1651d6bc46c1b103944b32ce..046c1efe67952007b3875d5b418302adf092b45a 100644 --- a/gcc/ChangeLog +++ b/gcc/ChangeLog @@ -1,3 +1,63 @@ +2009-07-17 Richard Guenther <rguenther@suse.de> + + PR c/40401 + * tree-pass.h (pass_diagnose_omp_blocks): Declare. + (pass_warn_unused_result): Likewise. + (TODO_set_props): Remove. + * omp-low.c (diagnose_omp_structured_block_errors): Change to + run as a pass. + (pass_diagnose_omp_blocks): Define. + * c-decl.c (pop_file_scope): Do not finalize the CU here. + (c_gimple_diagnostics_recursively): Remove. + (finish_function): Do not call it. + (c_write_global_declarations): Continue after errors. + Finalize the CU here. + * c-gimplify.c (c_genericize): Do not gimplify here. + * c-common.c (c_warn_unused_result): Move ... + * tree-cfg.c (do_warn_unused_result): ... here. + (run_warn_unused_result): New function. + (gate_warn_unused_result): New function. + (pass_warn_unused_result): New pass. + * c-common.h (c_warn_unused_result): Remove. + * flags.h (flag_warn_unused_result): Declare. + * c-opts.c (c_common_init_options): Enable flag_warn_unused_result. + * opts.c (flag_warn_unused_result): Initialize to false. + * toplev.c (compile_file): Add comment. + * omp-low.c (create_omp_child_function): Do not register + the function with the frontend. + (diagnose_omp_structured_block_errors): Prepare to be + called as optimization pass. + (gate_diagnose_omp_blocks): New function. + (pass_diagnose_omp_blocks): New pass. + * cgraph.h (cgraph_optimize): Remove. + (cgraph_analyze_function): Likewise. + * cgraph.c (cgraph_add_new_function): Gimplify C++ thunks. + * cgraphunit.c (cgraph_lower_function): Lower nested functions + before their parents here. + (cgraph_finalize_function): Not here. + (cgraph_analyze_function): Gimplify functions here. + (cgraph_finalize_compilation_unit): Continue after errors. + Optimize the callgraph from here. + (cgraph_optimize): Make static. + * langhooks.c (write_global_declarations): Finalize the CU. + * gimplify.c (gimplify_asm_expr): Do not emit ASMs with errors. + (gimplify_function_tree): Assert we gimplify only once. + Set PROP_gimple_any property. + * tree-nested.c (gimplify_all_functions): New function. + (lower_nested_functions): Gimplify all nested functions. + * gimple.h (diagnose_omp_structured_block_errors): Remove. + * passes.c (init_optimization_passes): Add pass_warn_unused_result + and pass_diagnose_omp_blocks after gimplification. Do not + set TODO_set_props on all_lowering_passes. + (execute_one_pass): Do not handle TODO_set_props. + * Makefile.in (cgraphunit.o): Add $(TREE_DUMP_H) dependency. + (gimplify.o): Add tree-pass.h dependency. + * tree-inline.c (copy_statement_list): Properly copy STATEMENT_LIST. + (copy_tree_body_r): Properly handle TARGET_EXPR like SAVE_EXPR. + (unsave_r): Likewise. + * c-omp.c (c_finish_omp_atomic): Set DECL_CONTEXT on the + temporary variable. + 2009-07-17 Sandra Loosemore <sandra@codesourcery.com> * doc/service.texi (Service): Restore previously removed link, diff --git a/gcc/Makefile.in b/gcc/Makefile.in index 18f25d5529a0e222385b5e8bd53ac2241c1f00e6..efdeab69d3e04f886c30a03d6c33193f5c9b4c43 100644 --- a/gcc/Makefile.in +++ b/gcc/Makefile.in @@ -2394,7 +2394,7 @@ gimplify.o : gimplify.c $(CONFIG_H) $(SYSTEM_H) $(TREE_H) $(GIMPLE_H) \ $(LANGHOOKS_DEF_H) $(TREE_FLOW_H) $(CGRAPH_H) $(TIMEVAR_H) $(TM_H) \ coretypes.h $(EXCEPT_H) $(FLAGS_H) $(RTL_H) $(FUNCTION_H) $(EXPR_H) output.h \ $(GGC_H) gt-gimplify.h $(HASHTAB_H) $(TARGET_H) $(TOPLEV_H) $(OPTABS_H) \ - $(REAL_H) $(SPLAY_TREE_H) vec.h tree-iterator.h + $(REAL_H) $(SPLAY_TREE_H) vec.h tree-iterator.h tree-pass.h gimple-iterator.o : gimple-iterator.c $(CONFIG_H) $(SYSTEM_H) coretypes.h \ $(TREE_H) $(GIMPLE_H) $(TREE_FLOW_H) value-prof.h gimple-low.o : gimple-low.c $(CONFIG_H) $(SYSTEM_H) $(TREE_H) \ @@ -2683,7 +2683,7 @@ cgraphunit.o : cgraphunit.c $(CONFIG_H) $(SYSTEM_H) coretypes.h $(TM_H) \ $(TARGET_H) $(CGRAPH_H) intl.h pointer-set.h $(FUNCTION_H) $(GIMPLE_H) \ $(TREE_FLOW_H) $(TREE_PASS_H) debug.h $(DIAGNOSTIC_H) \ $(FIBHEAP_H) output.h $(PARAMS_H) $(RTL_H) $(TIMEVAR_H) $(IPA_PROP_H) \ - gt-cgraphunit.h tree-iterator.h $(COVERAGE_H) + gt-cgraphunit.h tree-iterator.h $(COVERAGE_H) $(TREE_DUMP_H) cgraphbuild.o : cgraphbuild.c $(CONFIG_H) $(SYSTEM_H) coretypes.h $(TM_H) \ $(TREE_H) langhooks.h $(CGRAPH_H) intl.h pointer-set.h $(GIMPLE_H) \ $(TREE_FLOW_H) $(TREE_PASS_H) diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog index 0e3c7785c280fcc03f1b373646defa171b93d24e..55de47c1300797bf46fadb0a968c77bc20dbec4e 100644 --- a/gcc/ada/ChangeLog +++ b/gcc/ada/ChangeLog @@ -1,3 +1,18 @@ +2009-07-17 Richard Guenther <rguenther@suse.de> + + PR c/40401 + * utils.c (end_subprog_body): Revert to pre-tuples state. Remove + unused parameter. + (gnat_gimplify_function): Do not gimplify here. + Fold into its only caller and remove. + (gnat_builtin_function): Adjust for end_subprog_body signature change. + (gnat_write_global_declarations): Also finalize the CU. + * misc.c (gnat_parse_file): Do not finalize the CU here. + * trans.c (gigi): Revert to pre-tuples state. + (Subprogram_Body_to_gnu): Adjust for end_subprog_body signature + change. + * gigi.h (end_subprog_body): Remove unused parameter. + 2009-07-15 Arnaud Charlet <charlet@adacore.com> * gcc-interface/Make-lang.in: Update dependencies diff --git a/gcc/ada/gcc-interface/gigi.h b/gcc/ada/gcc-interface/gigi.h index de253b8d9390d77daec70d1c8c5c7f943827db62..05a46869f6eb1b69c6c14b2d2c6903f95c1cd0d7 100644 --- a/gcc/ada/gcc-interface/gigi.h +++ b/gcc/ada/gcc-interface/gigi.h @@ -678,9 +678,8 @@ extern tree create_label_decl (tree label_name); extern void begin_subprog_body (tree subprog_decl); /* Finish the definition of the current subprogram BODY and compile it all the - way to assembler language output. ELAB_P tells if this is called for an - elaboration routine, to be entirely discarded if empty. */ -extern void end_subprog_body (tree body, bool elab_p); + way to assembler language output. */ +extern void end_subprog_body (tree body); /* Build a template of type TEMPLATE_TYPE from the array bounds of ARRAY_TYPE. EXPR is an expression that we can use to locate any PLACEHOLDER_EXPRs. diff --git a/gcc/ada/gcc-interface/misc.c b/gcc/ada/gcc-interface/misc.c index 587eab3379e80e3fa20dbbf1c04d394c76351a6a..4b68227e3cd2484e2c369dcba9352113558fbe1a 100644 --- a/gcc/ada/gcc-interface/misc.c +++ b/gcc/ada/gcc-interface/misc.c @@ -176,9 +176,6 @@ gnat_parse_file (int set_yydebug ATTRIBUTE_UNUSED) /* Call the front end. */ _ada_gnat1drv (); - - /* We always have a single compilation unit in Ada. */ - cgraph_finalize_compilation_unit (); } /* Decode all the language specific options that cannot be decoded by GCC. diff --git a/gcc/ada/gcc-interface/trans.c b/gcc/ada/gcc-interface/trans.c index 5b4e5e86318e8067f4f4552d07a3d9753d953479..12599675d83e6496d86f087e352f1092de108e9a 100644 --- a/gcc/ada/gcc-interface/trans.c +++ b/gcc/ada/gcc-interface/trans.c @@ -627,6 +627,7 @@ gigi (Node_Id gnat_root, int max_gnat_node, int number_name, for (info = elab_info_list; info; info = info->next) { tree gnu_body = DECL_SAVED_TREE (info->elab_proc); + tree gnu_stmts; /* Unshare SAVE_EXPRs between subprograms. These are not unshared by the gimplifier for obvious reasons, but it turns out that we need to @@ -638,14 +639,24 @@ gigi (Node_Id gnat_root, int max_gnat_node, int number_name, an upstream bug for which we would not change the outcome. */ walk_tree_without_duplicates (&gnu_body, unshare_save_expr, NULL); - /* Process the function as others, but for indicating this is an - elab proc, to be discarded if empty, then propagate the status - up to the GNAT tree node. */ - begin_subprog_body (info->elab_proc); - end_subprog_body (gnu_body, true); - if (empty_body_p (gimple_body (info->elab_proc))) - Set_Has_No_Elaboration_Code (info->gnat_node, 1); + /* We should have a BIND_EXPR, but it may or may not have any statements + in it. If it doesn't have any, we have nothing to do. */ + gnu_stmts = gnu_body; + if (TREE_CODE (gnu_stmts) == BIND_EXPR) + gnu_stmts = BIND_EXPR_BODY (gnu_stmts); + + /* If there are no statements, there is no elaboration code. */ + if (!gnu_stmts || !STATEMENT_LIST_HEAD (gnu_stmts)) + { + Set_Has_No_Elaboration_Code (info->gnat_node, 1); + } + else + { + /* Process the function as others. */ + begin_subprog_body (info->elab_proc); + end_subprog_body (gnu_body); + } } /* We cannot track the location of errors past this point. */ @@ -2326,7 +2337,7 @@ Subprogram_Body_to_gnu (Node_Id gnat_node) : Sloc (gnat_node)), &DECL_STRUCT_FUNCTION (gnu_subprog_decl)->function_end_locus); - end_subprog_body (gnu_result, false); + end_subprog_body (gnu_result); /* Finally annotate the parameters and disconnect the trees for parameters that we have turned into variables since they are now unusable. */ diff --git a/gcc/ada/gcc-interface/utils.c b/gcc/ada/gcc-interface/utils.c index aa12eb77506fd545ec682e8c6083fd791970c595..59d9477a44d22b187bd14aeb4da1a6b94bb7173f 100644 --- a/gcc/ada/gcc-interface/utils.c +++ b/gcc/ada/gcc-interface/utils.c @@ -203,7 +203,6 @@ static GTY((deletable)) tree free_block_chain; static tree merge_sizes (tree, tree, tree, bool, bool); static tree compute_related_constant (tree, tree); static tree split_plus (tree, tree *); -static void gnat_gimplify_function (tree); static tree float_type_for_precision (int, enum machine_mode); static tree convert_to_fat_pointer (tree, tree); static tree convert_to_thin_pointer (tree, tree); @@ -2070,11 +2069,10 @@ gnat_genericize (tree fndecl) } /* Finish the definition of the current subprogram BODY and compile it all the - way to assembler language output. ELAB_P tells if this is called for an - elaboration routine, to be entirely discarded if empty. */ + way to assembler language output. */ void -end_subprog_body (tree body, bool elab_p) +end_subprog_body (tree body) { tree fndecl = current_function_decl; @@ -2107,44 +2105,19 @@ end_subprog_body (tree body, bool elab_p) /* Perform the required pre-gimplification transformations on the tree. */ gnat_genericize (fndecl); + /* Dump functions before gimplification. */ + dump_function (TDI_original, fndecl); + /* We do different things for nested and non-nested functions. ??? This should be in cgraph. */ if (!DECL_CONTEXT (fndecl)) - { - gnat_gimplify_function (fndecl); - - /* If this is an empty elaboration proc, just discard the node. - Otherwise, compile further. */ - if (elab_p && empty_body_p (gimple_body (fndecl))) - cgraph_remove_node (cgraph_node (fndecl)); - else - cgraph_finalize_function (fndecl, false); - } + cgraph_finalize_function (fndecl, false); else /* Register this function with cgraph just far enough to get it added to our parent's nested function list. */ (void) cgraph_node (fndecl); } -/* Convert FNDECL's code to GIMPLE and handle any nested functions. */ - -static void -gnat_gimplify_function (tree fndecl) -{ - struct cgraph_node *cgn; - - dump_function (TDI_original, fndecl); - gimplify_function_tree (fndecl); - dump_function (TDI_generic, fndecl); - - /* Convert all nested functions to GIMPLE now. We do things in this order - so that items like VLA sizes are expanded properly in the context of the - correct function. */ - cgn = cgraph_node (fndecl); - for (cgn = cgn->nested; cgn; cgn = cgn->next_nested) - gnat_gimplify_function (cgn->decl); -} - tree gnat_builtin_function (tree decl) { @@ -3520,7 +3493,7 @@ build_function_stub (tree gnu_subprog, Entity_Id gnat_subprog) gnat_poplevel (); allocate_struct_function (gnu_stub_decl, false); - end_subprog_body (gnu_body, false); + end_subprog_body (gnu_body); } /* Build a type to be used to represent an aliased object whose nominal @@ -4693,7 +4666,7 @@ gnat_write_global_declarations (void) { /* Proceed to optimize and emit assembly. FIXME: shouldn't be the front end's responsibility to call this. */ - cgraph_optimize (); + cgraph_finalize_compilation_unit (); /* Emit debug info for all global declarations. */ emit_debug_global_declarations (VEC_address (tree, global_decls), diff --git a/gcc/c-common.c b/gcc/c-common.c index 3aa8ed95851a51ee6c91f6fdd05c7cd80430535b..328e0fdae8e8d6c3e4a4eef19fc24a77188ab9b8 100644 --- a/gcc/c-common.c +++ b/gcc/c-common.c @@ -8226,69 +8226,6 @@ c_cpp_error (cpp_reader *pfile ATTRIBUTE_UNUSED, int level, return ret; } -/* Walk a gimplified function and warn for functions whose return value is - ignored and attribute((warn_unused_result)) is set. This is done before - inlining, so we don't have to worry about that. */ - -void -c_warn_unused_result (gimple_seq seq) -{ - tree fdecl, ftype; - gimple_stmt_iterator i; - - for (i = gsi_start (seq); !gsi_end_p (i); gsi_next (&i)) - { - gimple g = gsi_stmt (i); - - switch (gimple_code (g)) - { - case GIMPLE_BIND: - c_warn_unused_result (gimple_bind_body (g)); - break; - case GIMPLE_TRY: - c_warn_unused_result (gimple_try_eval (g)); - c_warn_unused_result (gimple_try_cleanup (g)); - break; - case GIMPLE_CATCH: - c_warn_unused_result (gimple_catch_handler (g)); - break; - case GIMPLE_EH_FILTER: - c_warn_unused_result (gimple_eh_filter_failure (g)); - break; - - case GIMPLE_CALL: - if (gimple_call_lhs (g)) - break; - - /* This is a naked call, as opposed to a GIMPLE_CALL with an - LHS. All calls whose value is ignored should be - represented like this. Look for the attribute. */ - fdecl = gimple_call_fndecl (g); - ftype = TREE_TYPE (TREE_TYPE (gimple_call_fn (g))); - - if (lookup_attribute ("warn_unused_result", TYPE_ATTRIBUTES (ftype))) - { - location_t loc = gimple_location (g); - - if (fdecl) - warning_at (loc, OPT_Wunused_result, - "ignoring return value of %qD, " - "declared with attribute warn_unused_result", - fdecl); - else - warning_at (loc, OPT_Wunused_result, - "ignoring return value of function " - "declared with attribute warn_unused_result"); - } - break; - - default: - /* Not a container, not a call, or a call whose value is used. */ - break; - } - } -} - /* Convert a character from the host to the target execution character set. cpplib handles this, mostly. */ diff --git a/gcc/c-common.h b/gcc/c-common.h index 21d3648c70ba09210d8ab34ad3c451093d219222..d372e70631e6d74756252e95ecd77d9b88956ca1 100644 --- a/gcc/c-common.h +++ b/gcc/c-common.h @@ -982,8 +982,6 @@ extern void dump_time_statistics (void); extern bool c_dump_tree (void *, tree); -extern void c_warn_unused_result (gimple_seq); - extern void verify_sequence_points (tree); extern tree fold_offsetof (tree, tree); diff --git a/gcc/c-decl.c b/gcc/c-decl.c index 7ed646c257bb16e523607497e1c939e49ad78925..b594767d04c48835f7570efc48d1c4f390c49f66 100644 --- a/gcc/c-decl.c +++ b/gcc/c-decl.c @@ -1327,7 +1327,6 @@ pop_file_scope (void) file_scope = 0; maybe_apply_pending_pragma_weaks (); - cgraph_finalize_compilation_unit (); } /* Adjust the bindings for the start of a statement expression. */ @@ -7870,27 +7869,6 @@ store_parm_decls (void) cfun->dont_save_pending_sizes_p = 1; } -/* Emit diagnostics that require gimple input for detection. Operate on - FNDECL and all its nested functions. */ - -static void -c_gimple_diagnostics_recursively (tree fndecl) -{ - struct cgraph_node *cgn; - gimple_seq body = gimple_body (fndecl); - - /* Handle attribute((warn_unused_result)). Relies on gimple input. */ - c_warn_unused_result (body); - - /* Notice when OpenMP structured block constraints are violated. */ - if (flag_openmp) - diagnose_omp_structured_block_errors (fndecl); - - /* Finalize all nested functions now. */ - cgn = cgraph_node (fndecl); - for (cgn = cgn->nested; cgn ; cgn = cgn->next_nested) - c_gimple_diagnostics_recursively (cgn->decl); -} /* Finish up a function declaration and compile that function all the way to assembler language output. The free the storage @@ -7983,7 +7961,6 @@ finish_function (void) if (!decl_function_context (fndecl)) { c_genericize (fndecl); - c_gimple_diagnostics_recursively (fndecl); /* ??? Objc emits functions after finalizing the compilation unit. This should be cleaned up later and this conditional removed. */ @@ -9382,9 +9359,9 @@ c_write_global_declarations (void) if (pch_file) return; - /* Don't waste time on further processing if -fsyntax-only or we've - encountered errors. */ - if (flag_syntax_only || errorcount || sorrycount) + /* Don't waste time on further processing if -fsyntax-only. + Continue for warning and errors issued during lowering though. */ + if (flag_syntax_only) return; /* Close the external scope. */ @@ -9412,7 +9389,7 @@ c_write_global_declarations (void) /* We're done parsing; proceed to optimize and emit assembly. FIXME: shouldn't be the front end's responsibility to call this. */ - cgraph_optimize (); + cgraph_finalize_compilation_unit (); /* After cgraph has had a chance to emit everything that's going to be emitted, output debug information for globals. */ diff --git a/gcc/c-gimplify.c b/gcc/c-gimplify.c index 6595fc8fa03de5727ff7bd39c5cae68b7cf0d0b2..e50050c2324cff5e7a71792e95a49b4c2b804add 100644 --- a/gcc/c-gimplify.c +++ b/gcc/c-gimplify.c @@ -103,14 +103,7 @@ c_genericize (tree fndecl) dump_end (TDI_original, dump_orig); } - /* Go ahead and gimplify for now. */ - gimplify_function_tree (fndecl); - - dump_function (TDI_generic, fndecl); - - /* Genericize all nested functions now. We do things in this order so - that items like VLA sizes are expanded properly in the context of - the correct function. */ + /* Dump all nested functions now. */ cgn = cgraph_node (fndecl); for (cgn = cgn->nested; cgn ; cgn = cgn->next_nested) c_genericize (cgn->decl); diff --git a/gcc/c-omp.c b/gcc/c-omp.c index b949501d52b0750228788a9a7753e22ea6ca2a29..6445e5d42eea0ab4b13833e556f9b2ce07b84e51 100644 --- a/gcc/c-omp.c +++ b/gcc/c-omp.c @@ -142,6 +142,7 @@ c_finish_omp_atomic (location_t loc, enum tree_code code, tree lhs, tree rhs) /* Make sure LHS is simple enough so that goa_lhs_expr_p can recognize it even after unsharing function body. */ tree var = create_tmp_var_raw (TREE_TYPE (addr), NULL); + DECL_CONTEXT (var) = current_function_decl; addr = build4 (TARGET_EXPR, TREE_TYPE (addr), var, addr, NULL, NULL); } lhs = build_indirect_ref (loc, addr, NULL); diff --git a/gcc/c-opts.c b/gcc/c-opts.c index 4574bb2e92080bd7ec2e88712ad0bba124ac82d3..3b9b34bdc3f7e88ecce82cbeb9a6a889a8ae32a9 100644 --- a/gcc/c-opts.c +++ b/gcc/c-opts.c @@ -232,6 +232,7 @@ c_common_init_options (unsigned int argc, const char **argv) flag_exceptions = c_dialect_cxx (); warn_pointer_arith = c_dialect_cxx (); warn_write_strings = c_dialect_cxx(); + flag_warn_unused_result = true; /* By default, C99-like requirements for complex multiply and divide. */ flag_complex_method = 2; diff --git a/gcc/cgraph.c b/gcc/cgraph.c index 4b3a962fbd3e06919dd32c4283422eeadcc95e14..3d0fee5ba941875bb607c9c70f564967d5e67d4e 100644 --- a/gcc/cgraph.c +++ b/gcc/cgraph.c @@ -1836,6 +1836,9 @@ cgraph_add_new_function (tree fndecl, bool lowered) push_cfun (DECL_STRUCT_FUNCTION (fndecl)); current_function_decl = fndecl; gimple_register_cfg_hooks (); + /* C++ Thunks are emitted late via this function, gimplify them. */ + if (!gimple_body (fndecl)) + gimplify_function_tree (fndecl); tree_lowering_passes (fndecl); bitmap_obstack_initialize (NULL); if (!gimple_in_ssa_p (DECL_STRUCT_FUNCTION (fndecl))) diff --git a/gcc/cgraph.h b/gcc/cgraph.h index bf3f320e4f32d5d6ea5cb77167228abe84c9f176..3e9a6d4201c6f2af2ee9d9320ac3b512c38b70bb 100644 --- a/gcc/cgraph.h +++ b/gcc/cgraph.h @@ -426,7 +426,6 @@ struct cgraph_node * cgraph_create_virtual_clone (struct cgraph_node *old_node, void cgraph_finalize_function (tree, bool); void cgraph_mark_if_needed (tree); void cgraph_finalize_compilation_unit (void); -void cgraph_optimize (void); void cgraph_mark_needed_node (struct cgraph_node *); void cgraph_mark_address_taken_node (struct cgraph_node *); void cgraph_mark_reachable_node (struct cgraph_node *); @@ -442,7 +441,6 @@ struct cgraph_node *cgraph_function_versioning (struct cgraph_node *, VEC(ipa_replace_map_p,gc)*, bitmap); void tree_function_versioning (tree, tree, VEC (ipa_replace_map_p,gc)*, bool, bitmap); -void cgraph_analyze_function (struct cgraph_node *); struct cgraph_node *save_inline_function_body (struct cgraph_node *); void record_references_in_initializer (tree); bool cgraph_process_new_functions (void); diff --git a/gcc/cgraphunit.c b/gcc/cgraphunit.c index 0a3cc6c3811bfca3969eeea7c4cbc758a1732e0f..d329dc1c0a2a4f4ae5c5068e7275693429a6e5a2 100644 --- a/gcc/cgraphunit.c +++ b/gcc/cgraphunit.c @@ -132,6 +132,7 @@ along with GCC; see the file COPYING3. If not see #include "gimple.h" #include "tree-iterator.h" #include "tree-pass.h" +#include "tree-dump.h" #include "output.h" #include "coverage.h" @@ -139,6 +140,8 @@ static void cgraph_expand_all_functions (void); static void cgraph_mark_functions_to_output (void); static void cgraph_expand_function (struct cgraph_node *); static void cgraph_output_pending_asms (void); +static void cgraph_optimize (void); +static void cgraph_analyze_function (struct cgraph_node *); static FILE *cgraph_dump_file; @@ -490,6 +493,11 @@ cgraph_lower_function (struct cgraph_node *node) { if (node->lowered) return; + + if (node->nested) + lower_nested_functions (node->decl); + gcc_assert (!node->nested); + tree_lowering_passes (node->decl); node->lowered = true; } @@ -513,9 +521,6 @@ cgraph_finalize_function (tree decl, bool nested) node->lowered = DECL_STRUCT_FUNCTION (decl)->cfg != NULL; node->finalized_by_frontend = true; record_cdtor_fn (node->decl); - if (node->nested) - lower_nested_functions (decl); - gcc_assert (!node->nested); if (decide_is_function_needed (node, decl)) cgraph_mark_needed_node (node); @@ -789,18 +794,28 @@ cgraph_output_pending_asms (void) } /* Analyze the function scheduled to be output. */ -void +static void cgraph_analyze_function (struct cgraph_node *node) { + tree save = current_function_decl; tree decl = node->decl; current_function_decl = decl; push_cfun (DECL_STRUCT_FUNCTION (decl)); + + /* Make sure to gimplify bodies only once. During analyzing a + function we lower it, which will require gimplified nested + functions, so we can end up here with an already gimplified + body. */ + if (!gimple_body (decl)) + gimplify_function_tree (decl); + dump_function (TDI_generic, decl); + cgraph_lower_function (node); node->analyzed = true; pop_cfun (); - current_function_decl = NULL; + current_function_decl = save; } /* Look for externally_visible and used attributes and mark cgraph nodes @@ -935,8 +950,6 @@ cgraph_analyze_functions (void) } gcc_assert (!node->analyzed && node->reachable); - gcc_assert (gimple_body (decl)); - cgraph_analyze_function (node); for (edge = node->callees; edge; edge = edge->next_callee) @@ -1010,8 +1023,8 @@ cgraph_analyze_functions (void) void cgraph_finalize_compilation_unit (void) { - if (errorcount || sorrycount) - return; + /* Do not skip analyzing the functions if there were errors, we + miss diagnostics for following functions otherwise. */ finalize_size_functions (); finish_aliases_1 (); @@ -1025,6 +1038,8 @@ cgraph_finalize_compilation_unit (void) timevar_push (TV_CGRAPH); cgraph_analyze_functions (); timevar_pop (TV_CGRAPH); + + cgraph_optimize (); } @@ -1311,7 +1326,7 @@ ipa_passes (void) /* Perform simple optimizations based on callgraph. */ -void +static void cgraph_optimize (void) { if (errorcount || sorrycount) diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog index 43d3fa4a20ab5da5a79ab2e7e504ca3fd8ce800a..520ae54629fe8fac96b420c7e9c0aa7ed09491e4 100644 --- a/gcc/cp/ChangeLog +++ b/gcc/cp/ChangeLog @@ -1,3 +1,20 @@ +2009-07-17 Richard Guenther <rguenther@suse.de> + + PR c/40401 + * decl.c (finish_function): Do not emit unused result warnings + from here. + * cp-objcp-common.h (LANG_HOOKS_POST_GIMPLIFY_PASS): Use + c_warn_unused_result_pass. + * semantics.c (expand_or_defer_fn): Adjust assertion about IL status. + * optimize.c (clone_body): Clone in GENERIC. + (maybe_clone_body): Do not clear DECL_SAVED_TREE. + * decl2.c (cp_write_global_declarations): Fix body test. + Do not call cgraph_optimize. + * Make-lang.in (optimize.o): Add tree-iterator.h dependency. + * method.c (use_thunk): Register thunk with + cgraph_finalize_function. + * error.c (function_category): Guard access of DECL_LANG_SPECIFIC. + 2009-07-17 Richard Guenther <rguenther@suse.de> * init.c (build_vec_delete_1): Do not set DECL_REGISTER on the diff --git a/gcc/cp/Make-lang.in b/gcc/cp/Make-lang.in index 6bff698f00b25b0e682f343e67f6b7b426ce67dc..c7d1a449a901487499772cda5cac8e9885d4262c 100644 --- a/gcc/cp/Make-lang.in +++ b/gcc/cp/Make-lang.in @@ -303,7 +303,7 @@ cp/semantics.o: cp/semantics.c $(CXX_TREE_H) $(TM_H) except.h toplev.h \ cp/dump.o: cp/dump.c $(CXX_TREE_H) $(TM_H) $(TREE_DUMP_H) cp/optimize.o: cp/optimize.c $(CXX_TREE_H) $(TM_H) rtl.h $(INTEGRATE_H) \ insn-config.h input.h $(PARAMS_H) debug.h $(TREE_INLINE_H) $(GIMPLE_H) \ - $(TARGET_H) + $(TARGET_H) tree-iterator.h cp/mangle.o: cp/mangle.c $(CXX_TREE_H) $(TM_H) toplev.h $(REAL_H) \ gt-cp-mangle.h $(TARGET_H) $(TM_P_H) cp/parser.o: cp/parser.c $(CXX_TREE_H) $(TM_H) $(DIAGNOSTIC_H) gt-cp-parser.h \ diff --git a/gcc/cp/decl.c b/gcc/cp/decl.c index e65e6360cb6a409373a6cb34e2d408873f61e187..251d0a3a5d2b92cc9b61214af1fb218028d13449 100644 --- a/gcc/cp/decl.c +++ b/gcc/cp/decl.c @@ -12434,9 +12434,6 @@ finish_function (int flags) f->x_return_value = NULL; f->bindings = NULL; f->extern_decl_map = NULL; - - /* Handle attribute((warn_unused_result)). Relies on gimple input. */ - c_warn_unused_result (gimple_body (fndecl)); } /* Clear out the bits we don't need. */ local_names = NULL; diff --git a/gcc/cp/decl2.c b/gcc/cp/decl2.c index 3a5d2fa929bdc5bae3251a9ce54e5ed150c59d25..df79e9c4e1c0d3ed6be40b6a0445f5d0e00e7b3f 100644 --- a/gcc/cp/decl2.c +++ b/gcc/cp/decl2.c @@ -3518,7 +3518,7 @@ cp_write_global_declarations (void) reconsider = true; } - if (!gimple_body (decl)) + if (!DECL_SAVED_TREE (decl)) continue; /* We lie to the back end, pretending that some functions @@ -3640,7 +3640,6 @@ cp_write_global_declarations (void) pop_lang_context (); cgraph_finalize_compilation_unit (); - cgraph_optimize (); /* Now, issue warnings about static, but not defined, functions, etc., and emit debugging information. */ diff --git a/gcc/cp/error.c b/gcc/cp/error.c index 939400bd2c42660550cd5c720cb3469c4fa55d6f..c5310ff6ca05071a8819ab28606c39719c8a7728 100644 --- a/gcc/cp/error.c +++ b/gcc/cp/error.c @@ -2647,7 +2647,11 @@ cp_print_error_function (diagnostic_context *context, static const char * function_category (tree fn) { - if (DECL_FUNCTION_MEMBER_P (fn)) + /* We can get called from the middle-end for diagnostics of function + clones. Make sure we have language specific information before + dereferencing it. */ + if (DECL_LANG_SPECIFIC (STRIP_TEMPLATE (fn)) + && DECL_FUNCTION_MEMBER_P (fn)) { if (DECL_STATIC_FUNCTION_P (fn)) return _("In static member function %qs"); diff --git a/gcc/cp/optimize.c b/gcc/cp/optimize.c index 9d4a8c5f8e4ffe0e652f8570478abed3efc7a6dc..c9d6cebb817811166fddf4f4a9fbd1b59a8df170 100644 --- a/gcc/cp/optimize.c +++ b/gcc/cp/optimize.c @@ -41,6 +41,7 @@ along with GCC; see the file COPYING3. If not see #include "diagnostic.h" #include "tree-dump.h" #include "gimple.h" +#include "tree-iterator.h" /* Prototypes. */ @@ -81,10 +82,7 @@ static void clone_body (tree clone, tree fn, void *arg_map) { copy_body_data id; - gimple_seq new_body; - - /* FN must already be in GIMPLE form. */ - gcc_assert (gimple_body (fn)); + tree stmts; /* Clone the body, as if we were making an inline call. But, remap the parameters in the callee to the parameters of caller. */ @@ -103,9 +101,9 @@ clone_body (tree clone, tree fn, void *arg_map) /* We're not inside any EH region. */ id.eh_region = -1; - /* Actually copy the body. */ - new_body = remap_gimple_seq (gimple_body (fn), &id); - gimple_set_body (clone, new_body); + stmts = DECL_SAVED_TREE (fn); + walk_tree (&stmts, copy_tree_body_r, &id, NULL); + append_to_statement_list_force (stmts, &DECL_SAVED_TREE (clone)); } /* FN is a function that has a complete body. Clone the body as @@ -208,7 +206,8 @@ maybe_clone_body (tree fn) } /* Otherwise, map the VTT parameter to `NULL'. */ else - *pointer_map_insert (decl_map, parm) = null_pointer_node; + *pointer_map_insert (decl_map, parm) + = fold_convert (TREE_TYPE (parm), null_pointer_node); } /* Map other parameters to their equivalents in the cloned function. */ @@ -237,7 +236,6 @@ maybe_clone_body (tree fn) /* Now, expand this function into RTL, if appropriate. */ finish_function (0); BLOCK_ABSTRACT_ORIGIN (DECL_INITIAL (clone)) = DECL_INITIAL (fn); - DECL_SAVED_TREE (clone) = NULL; expand_or_defer_fn (clone); first = false; } diff --git a/gcc/cp/semantics.c b/gcc/cp/semantics.c index 9ac88fd7b65d80d09d9da36e66190d0dad69a0b1..23db832143179853b15c2ead55ffc4bd6f984e53 100644 --- a/gcc/cp/semantics.c +++ b/gcc/cp/semantics.c @@ -3230,7 +3230,7 @@ expand_or_defer_fn (tree fn) return; } - gcc_assert (gimple_body (fn)); + gcc_assert (DECL_SAVED_TREE (fn)); /* If this is a constructor or destructor body, we have to clone it. */ diff --git a/gcc/flags.h b/gcc/flags.h index 42158de0015e4d02159e8f7ff3f605306305e3a0..8b71302f3e4a66c4da514430cb0ccd5bc8720243 100644 --- a/gcc/flags.h +++ b/gcc/flags.h @@ -250,6 +250,9 @@ extern bool g_switch_set; /* Same for selective scheduling. */ extern bool sel_sched_switch_set; +/* Whether to run the warn_unused_result attribute pass. */ +extern bool flag_warn_unused_result; + /* Values of the -falign-* flags: how much to align labels in code. 0 means `use default', 1 means `don't align'. For each variable, there is an _log variant which is the power diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog index 953e681dd8ef6c0624583cb85ca67006f2d0e14b..44289a6b66e5e6057b61a391fc99748efe626143 100644 --- a/gcc/fortran/ChangeLog +++ b/gcc/fortran/ChangeLog @@ -1,3 +1,12 @@ +2009-07-17 Richard Guenther <rguenther@suse.de> + + PR c/40401 + * f95-lang.c (gfc_be_parse_file): Do not finalize the CU here. + * trans-decl.c (gfc_gimplify_function): Remove. + (build_entry_thunks): Do not gimplify here. + (create_main_function): Likewise. + (gfc_generate_function_code): Likewise. + 2009-07-17 Aldy Hernandez <aldyh@redhat.com> Manuel López-Ibáñez <manu@gcc.gnu.org> diff --git a/gcc/fortran/f95-lang.c b/gcc/fortran/f95-lang.c index 97a071d06f9d182cc9174a31b87a59e1c309de68..f9d1878d379f5c339bf6cfb31191b3742023636a 100644 --- a/gcc/fortran/f95-lang.c +++ b/gcc/fortran/f95-lang.c @@ -241,9 +241,6 @@ gfc_be_parse_file (int set_yydebug ATTRIBUTE_UNUSED) gfc_parse_file (); gfc_generate_constructors (); - cgraph_finalize_compilation_unit (); - cgraph_optimize (); - /* Tell the frontend about any errors. */ gfc_get_errors (&warnings, &errors); errorcount += errors; diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c index 5ea24c54b458fb16fced158371582a1f753feaf8..5133888fa134bf67d3eafa0ee2ff07d68539b62b 100644 --- a/gcc/fortran/trans-decl.c +++ b/gcc/fortran/trans-decl.c @@ -1839,30 +1839,6 @@ create_function_arglist (gfc_symbol * sym) DECL_ARGUMENTS (fndecl) = arglist; } -/* Convert FNDECL's code to GIMPLE and handle any nested functions. */ - -static void -gfc_gimplify_function (tree fndecl) -{ - struct cgraph_node *cgn; - - gimplify_function_tree (fndecl); - dump_function (TDI_generic, fndecl); - - /* Generate errors for structured block violations. */ - /* ??? Could be done as part of resolve_labels. */ - if (flag_openmp) - diagnose_omp_structured_block_errors (fndecl); - - /* Convert all nested functions to GIMPLE now. We do things in this order - so that items like VLA sizes are expanded properly in the context of the - correct function. */ - cgn = cgraph_node (fndecl); - for (cgn = cgn->nested; cgn; cgn = cgn->next_nested) - gfc_gimplify_function (cgn->decl); -} - - /* Do the setup necessary before generating the body of a function. */ static void @@ -2060,7 +2036,6 @@ build_entry_thunks (gfc_namespace * ns) current_function_decl = NULL_TREE; - gfc_gimplify_function (thunk_fndecl); cgraph_finalize_function (thunk_fndecl, false); /* We share the symbols in the formal argument list with other entry @@ -4142,7 +4117,6 @@ create_main_function (tree fndecl) /* Output the GENERIC tree. */ dump_function (TDI_original, ftn_main); - gfc_gimplify_function (ftn_main); cgraph_finalize_function (ftn_main, false); if (old_context) @@ -4414,10 +4388,7 @@ gfc_generate_function_code (gfc_namespace * ns) added to our parent's nested function list. */ (void) cgraph_node (fndecl); else - { - gfc_gimplify_function (fndecl); - cgraph_finalize_function (fndecl, false); - } + cgraph_finalize_function (fndecl, false); gfc_trans_use_stmts (ns); gfc_traverse_ns (ns, gfc_emit_parameter_debug_info); diff --git a/gcc/gimple.h b/gcc/gimple.h index 0f8b1c86bd63f60a7593df3da6e012672ded3082..2f16c60538a2089d01d84215a6eb63590e8ecc5e 100644 --- a/gcc/gimple.h +++ b/gcc/gimple.h @@ -979,7 +979,6 @@ extern gimple_predicate rhs_predicate_for (tree); extern tree canonicalize_cond_expr_cond (tree); /* In omp-low.c. */ -extern void diagnose_omp_structured_block_errors (tree); extern tree omp_reduction_init (tree, tree); /* In tree-nested.c. */ diff --git a/gcc/gimplify.c b/gcc/gimplify.c index db7de3b573b6baca91733fde39326a2bb3af76b3..884d00f07220feaa52c48684bb7585e3c4f25fa7 100644 --- a/gcc/gimplify.c +++ b/gcc/gimplify.c @@ -52,6 +52,7 @@ along with GCC; see the file COPYING3. If not see #include "splay-tree.h" #include "vec.h" #include "gimple.h" +#include "tree-pass.h" enum gimplify_omp_var_data @@ -4913,14 +4914,18 @@ gimplify_asm_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p) for (link = ASM_CLOBBERS (expr); link; ++i, link = TREE_CHAIN (link)) VEC_safe_push (tree, gc, clobbers, link); - - stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)), - inputs, outputs, clobbers); - gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr)); - gimple_asm_set_input (stmt, ASM_INPUT_P (expr)); + /* Do not add ASMs with errors to the gimple IL stream. */ + if (ret != GS_ERROR) + { + stmt = gimple_build_asm_vec (TREE_STRING_POINTER (ASM_STRING (expr)), + inputs, outputs, clobbers); - gimplify_seq_add_stmt (pre_p, stmt); + gimple_asm_set_volatile (stmt, ASM_VOLATILE_P (expr)); + gimple_asm_set_input (stmt, ASM_INPUT_P (expr)); + + gimplify_seq_add_stmt (pre_p, stmt); + } return ret; } @@ -7482,6 +7487,8 @@ gimplify_function_tree (tree fndecl) gimple_seq seq; gimple bind; + gcc_assert (!gimple_body (fndecl)); + oldfn = current_function_decl; current_function_decl = fndecl; if (DECL_STRUCT_FUNCTION (fndecl)) @@ -7548,6 +7555,7 @@ gimplify_function_tree (tree fndecl) } DECL_SAVED_TREE (fndecl) = NULL_TREE; + cfun->curr_properties = PROP_gimple_any; current_function_decl = oldfn; pop_cfun (); diff --git a/gcc/java/ChangeLog b/gcc/java/ChangeLog index 9e7e5f517eb1de60facf2c0d4802bb578d2ed19c..d6c87f45a10af7400821f34af073f40a2ec72a56 100644 --- a/gcc/java/ChangeLog +++ b/gcc/java/ChangeLog @@ -1,3 +1,18 @@ +2009-07-17 Richard Guenther <rguenther@suse.de> + + PR c/40401 + * java-gimplify.c (java_genericize): Do not gimplify here. + But replace all local references. + (java_gimplify_expr): Do not replace local references here. + (java_gimplify_modify_expr): Likewise. + * jcf-parse.c (java_parse_file): Do not finalize the CU or + optimize the cgraph here. + * decl.c (java_replace_reference): Make static. + (java_replace_references): New function. + (end_java_method): Clear base_decl_map. + * java-tree.h (java_replace_references): Declare. + (java_replace_reference): Remove. + 2009-07-14 Taras Glek <tglek@mozilla.com> Rafael Espindola <espindola@google.com> diff --git a/gcc/java/decl.c b/gcc/java/decl.c index 3c1e7eaef9cd62907043c56689694f2302da7efe..8c327fa97d3d369760aecb6b4a3f5f925f7f12ae 100644 --- a/gcc/java/decl.c +++ b/gcc/java/decl.c @@ -306,13 +306,13 @@ find_local_variable (int index, tree type, int pc ATTRIBUTE_UNUSED) return decl; } -/* Called during gimplification for every variable. If the variable +/* Called during genericization for every variable. If the variable is a temporary of pointer type, replace it with a common variable thath is used to hold all pointer types that are ever stored in that slot. Set WANT_LVALUE if you want a variable that is to be written to. */ -tree +static tree java_replace_reference (tree var_decl, bool want_lvalue) { tree decl_type; @@ -341,6 +341,39 @@ java_replace_reference (tree var_decl, bool want_lvalue) return var_decl; } +/* Helper for java_genericize. */ + +tree +java_replace_references (tree *tp, int *walk_subtrees, + void *data ATTRIBUTE_UNUSED) +{ + if (TREE_CODE (*tp) == MODIFY_EXPR) + { + tree lhs = TREE_OPERAND (*tp, 0); + /* This is specific to the bytecode compiler. If a variable has + LOCAL_SLOT_P set, replace an assignment to it with an assignment + to the corresponding variable that holds all its aliases. */ + if (TREE_CODE (lhs) == VAR_DECL + && DECL_LANG_SPECIFIC (lhs) + && LOCAL_SLOT_P (lhs) + && TREE_CODE (TREE_TYPE (lhs)) == POINTER_TYPE) + { + tree new_lhs = java_replace_reference (lhs, /* want_lvalue */ true); + tree new_rhs = build1 (NOP_EXPR, TREE_TYPE (new_lhs), + TREE_OPERAND (*tp, 1)); + *tp = build2 (MODIFY_EXPR, TREE_TYPE (new_lhs), + new_lhs, new_rhs); + *tp = build1 (NOP_EXPR, TREE_TYPE (lhs), *tp); + } + } + if (TREE_CODE (*tp) == VAR_DECL) + { + *tp = java_replace_reference (*tp, /* want_lvalue */ false); + *walk_subtrees = 0; + } + + return NULL_TREE; +} /* Same as find_local_index, except that INDEX is a stack index. */ @@ -1877,6 +1910,7 @@ end_java_method (void) finish_method (fndecl); current_function_decl = NULL_TREE; + base_decl_map = NULL_TREE; } /* Prepare a method for expansion. */ diff --git a/gcc/java/java-gimplify.c b/gcc/java/java-gimplify.c index c460e5b094187157bcd8fa197f1ad3f55c8fae86..dd75fb995c29f2900f98f9ba730be5dc18ceac4a 100644 --- a/gcc/java/java-gimplify.c +++ b/gcc/java/java-gimplify.c @@ -44,12 +44,8 @@ static void dump_java_tree (enum tree_dump_index, tree); void java_genericize (tree fndecl) { + walk_tree (&DECL_SAVED_TREE (fndecl), java_replace_references, NULL, NULL); dump_java_tree (TDI_original, fndecl); - - /* Genericize with the gimplifier. */ - gimplify_function_tree (fndecl); - - dump_function (TDI_generic, fndecl); } /* Gimplify a Java tree. */ @@ -65,23 +61,9 @@ java_gimplify_expr (tree *expr_p, gimple_seq *pre_p, gimple_seq *post_p) *expr_p = java_gimplify_block (*expr_p); break; - case VAR_DECL: - *expr_p = java_replace_reference (*expr_p, /* want_lvalue */ false); - return GS_UNHANDLED; - case MODIFY_EXPR: return java_gimplify_modify_expr (expr_p); - case SAVE_EXPR: - /* Note that we can see <save_expr NULL> if the save_expr was - already handled by gimplify_save_expr. */ - if (TREE_OPERAND (*expr_p, 0) != NULL_TREE - && TREE_CODE (TREE_OPERAND (*expr_p, 0)) == VAR_DECL) - TREE_OPERAND (*expr_p, 0) - = java_replace_reference (TREE_OPERAND (*expr_p, 0), - /* want_lvalue */ false); - return GS_UNHANDLED; - case POSTINCREMENT_EXPR: case POSTDECREMENT_EXPR: case PREINCREMENT_EXPR: @@ -110,27 +92,12 @@ java_gimplify_modify_expr (tree *modify_expr_p) tree rhs = TREE_OPERAND (modify_expr, 1); tree lhs_type = TREE_TYPE (lhs); - /* This is specific to the bytecode compiler. If a variable has - LOCAL_SLOT_P set, replace an assignment to it with an assignment - to the corresponding variable that holds all its aliases. */ - if (TREE_CODE (lhs) == VAR_DECL - && DECL_LANG_SPECIFIC (lhs) - && LOCAL_SLOT_P (lhs) - && TREE_CODE (lhs_type) == POINTER_TYPE) - { - tree new_lhs = java_replace_reference (lhs, /* want_lvalue */ true); - tree new_rhs = build1 (NOP_EXPR, TREE_TYPE (new_lhs), rhs); - modify_expr = build2 (MODIFY_EXPR, TREE_TYPE (new_lhs), - new_lhs, new_rhs); - modify_expr = build1 (NOP_EXPR, lhs_type, modify_expr); - } - else if (lhs_type != TREE_TYPE (rhs)) + if (lhs_type != TREE_TYPE (rhs)) /* Fix up type mismatches to make legal GIMPLE. These are generated in several places, in particular null pointer assignment and subclass assignment. */ TREE_OPERAND (modify_expr, 1) = convert (lhs_type, rhs); - *modify_expr_p = modify_expr; return GS_UNHANDLED; } diff --git a/gcc/java/java-tree.h b/gcc/java/java-tree.h index 6bf2ecd8217d2cffd5df42c6a335cf3b9db69533..e68b136db711e208acfd0c5794b722c3a1ab4ae5 100644 --- a/gcc/java/java-tree.h +++ b/gcc/java/java-tree.h @@ -1119,7 +1119,7 @@ extern int find_class_or_string_constant (struct CPool *, int, tree); extern tree pushdecl_top_level (tree); extern tree pushdecl_function_level (tree); -extern tree java_replace_reference (tree, bool); +extern tree java_replace_references (tree *, int *, void *); extern int alloc_class_constant (tree); extern void init_expr_processing (void); extern void push_super_field (tree, tree); diff --git a/gcc/java/jcf-parse.c b/gcc/java/jcf-parse.c index f7b2cb20896a7efb6aa2e6a7f4c84812096eeef8..1a2de9ee8b0c962a217b5ad5456f1546b41d36d9 100644 --- a/gcc/java/jcf-parse.c +++ b/gcc/java/jcf-parse.c @@ -1982,11 +1982,6 @@ java_parse_file (int set_yydebug ATTRIBUTE_UNUSED) /* Arrange for any necessary initialization to happen. */ java_emit_static_constructor (); gcc_assert (global_bindings_p ()); - - /* Only finalize the compilation unit after we've told cgraph which - functions have their addresses stored. */ - cgraph_finalize_compilation_unit (); - cgraph_optimize (); } diff --git a/gcc/langhooks.c b/gcc/langhooks.c index ff20dd166006b2d7d0e2b7c0fae6d468d76e6ec2..194993f7ab342aa440acecaff14386df32513cb2 100644 --- a/gcc/langhooks.c +++ b/gcc/langhooks.c @@ -37,6 +37,7 @@ along with GCC; see the file COPYING3. If not see #include "langhooks-def.h" #include "ggc.h" #include "diagnostic.h" +#include "cgraph.h" /* Do nothing; in many cases the default hook. */ @@ -305,15 +306,20 @@ lhd_decl_ok_for_sibcall (const_tree decl ATTRIBUTE_UNUSED) void write_global_declarations (void) { + tree globals, decl, *vec; + int len, i; + + /* This lang hook is dual-purposed, and also finalizes the + compilation unit. */ + cgraph_finalize_compilation_unit (); + /* Really define vars that have had only a tentative definition. Really output inline functions that must actually be callable and have not been output so far. */ - tree globals = lang_hooks.decls.getdecls (); - int len = list_length (globals); - tree *vec = XNEWVEC (tree, len); - int i; - tree decl; + globals = lang_hooks.decls.getdecls (); + len = list_length (globals); + vec = XNEWVEC (tree, len); /* Process the decls in reverse order--earliest first. Put them into VEC from back to front, then take out from front. */ diff --git a/gcc/omp-low.c b/gcc/omp-low.c index 1c20931cf75efa4aa55a21b291d9d442ea43a533..82827bf762a647d912d8e3f9fde0ade6e43810ac 100644 --- a/gcc/omp-low.c +++ b/gcc/omp-low.c @@ -1572,7 +1572,6 @@ create_omp_child_function (omp_context *ctx, bool task_copy) decl = build_decl (gimple_location (ctx->stmt), FUNCTION_DECL, name, type); - decl = lang_hooks.decls.pushdecl (decl); if (!task_copy) ctx->cb.dst_fn = decl; @@ -6895,16 +6894,11 @@ diagnose_sb_2 (gimple_stmt_iterator *gsi_p, bool *handled_ops_p, return NULL_TREE; } -void -diagnose_omp_structured_block_errors (tree fndecl) +static unsigned int +diagnose_omp_structured_block_errors (void) { - tree save_current = current_function_decl; struct walk_stmt_info wi; - struct function *old_cfun = cfun; - gimple_seq body = gimple_body (fndecl); - - current_function_decl = fndecl; - set_cfun (DECL_STRUCT_FUNCTION (fndecl)); + gimple_seq body = gimple_body (current_function_decl); all_labels = splay_tree_new (splay_tree_compare_pointers, 0, 0); @@ -6918,8 +6912,32 @@ diagnose_omp_structured_block_errors (tree fndecl) splay_tree_delete (all_labels); all_labels = NULL; - set_cfun (old_cfun); - current_function_decl = save_current; + return 0; } +static bool +gate_diagnose_omp_blocks (void) +{ + return flag_openmp != 0; +} + +struct gimple_opt_pass pass_diagnose_omp_blocks = +{ + { + GIMPLE_PASS, + "diagnose_omp_blocks", /* name */ + gate_diagnose_omp_blocks, /* gate */ + diagnose_omp_structured_block_errors, /* execute */ + NULL, /* sub */ + NULL, /* next */ + 0, /* static_pass_number */ + TV_NONE, /* tv_id */ + PROP_gimple_any, /* properties_required */ + 0, /* properties_provided */ + 0, /* properties_destroyed */ + 0, /* todo_flags_start */ + 0, /* todo_flags_finish */ + } +}; + #include "gt-omp-low.h" diff --git a/gcc/opts.c b/gcc/opts.c index 94e70ba9676570dab74c215c257cb3f09939ebdb..33635dd979daa5d0b0dcd5bde84ef4abac1fe37a 100644 --- a/gcc/opts.c +++ b/gcc/opts.c @@ -362,6 +362,9 @@ DEF_VEC_ALLOC_P(const_char_p,heap); static VEC(const_char_p,heap) *ignored_options; +/* Language specific warning pass for unused results. */ +bool flag_warn_unused_result = false; + /* Input file names. */ const char **in_fnames; unsigned num_in_fnames; diff --git a/gcc/passes.c b/gcc/passes.c index bb52dc7eb3cbe9d0796a508462398717de6b8621..9ad672c477a85f3bc23df75e41645e34720cdd9b 100644 --- a/gcc/passes.c +++ b/gcc/passes.c @@ -509,6 +509,8 @@ init_optimization_passes (void) backend might produce already lowered functions that are not processed by these passes. */ p = &all_lowering_passes; + NEXT_PASS (pass_warn_unused_result); + NEXT_PASS (pass_diagnose_omp_blocks); NEXT_PASS (pass_remove_useless_stmts); NEXT_PASS (pass_mudflap_1); NEXT_PASS (pass_lower_omp); @@ -821,7 +823,6 @@ init_optimization_passes (void) /* Register the passes with the tree dump code. */ register_dump_files (all_lowering_passes, PROP_gimple_any); - all_lowering_passes->todo_flags_start |= TODO_set_props; register_dump_files (all_ipa_passes, PROP_gimple_any | PROP_gimple_lcf | PROP_gimple_leh | PROP_cfg); @@ -1261,9 +1262,6 @@ execute_one_pass (struct opt_pass *pass) if (!quiet_flag && !cfun) fprintf (stderr, " <%s>", pass->name ? pass->name : ""); - if (pass->todo_flags_start & TODO_set_props) - cfun->curr_properties = pass->properties_required; - /* Note that the folders should only create gimple expressions. This is a hack until the new folder is ready. */ in_gimple_form = (cfun && (cfun->curr_properties & PROP_trees)) != 0; diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog index d35fe72d9ff8d844b8c05cb13e965b40c8b6e335..3b704d52235718441f33dd3b98da6367570cd5fc 100644 --- a/gcc/testsuite/ChangeLog +++ b/gcc/testsuite/ChangeLog @@ -1,3 +1,24 @@ +2009-07-17 Richard Guenther <rguenther@suse.de> + + PR c/40401 + * g++.dg/rtti/crash4.C: New testcase. + * g++.dg/torture/20090706-1.C: Likewise. + * gcc.dg/redecl-17.c: Likewise. + * gfortran.dg/missing_optional_dummy_5.f90: Adjust pattern. + * gcc.dg/declspec-9.c: Expect extra error. + * gcc.dg/declspec-10.c: Likewise. + * gcc.dg/declspec-11.c: Likewise. + * gcc.dg/redecl-10.c: Expect extra warnings. + * gcc.target/i386/pr39082-1.c: Adjust diagnostic location. + * gcc.target/i386/pr39545-1.c: Likewise. + * g++.dg/ext/asm3.C: Expect more errors. + * g++.dg/gomp/block-1.C: Likewise. + * g++.dg/gomp/block-2.C: Likewise. + * g++.dg/gomp/block-3.C: Likewise. + * g++.dg/gomp/block-5.C: Likewise. + * g++.old-deja/g++.jason/report.C: Expect extra warnings. + * g++.dg/warn/unused-result1.C: XFAIL. + 2009-07-17 Richard Guenther <rguenther@suse.de> PR tree-optimization/40321 diff --git a/gcc/testsuite/g++.dg/ext/asm3.C b/gcc/testsuite/g++.dg/ext/asm3.C index 5eff16ffe7cb98121cdb520524c7d2351e723c0d..090218fe61f9fe9a505ed01a662067a11e968830 100644 --- a/gcc/testsuite/g++.dg/ext/asm3.C +++ b/gcc/testsuite/g++.dg/ext/asm3.C @@ -8,6 +8,8 @@ int two(int in) { register int out; - __asm__ ("" : "r" (out) : "r" (in)); // { dg-error "" "" } + __asm__ ("" : "r" (out) : "r" (in)); return out; } + +// { dg-message "error:" "" { target *-*-* } 11 } diff --git a/gcc/testsuite/g++.dg/gomp/block-1.C b/gcc/testsuite/g++.dg/gomp/block-1.C index 50a8c0e9ead48fbd6601a360b6a55a5e85783a1e..d2b86645af8d66eac5214602585cedce9d2c0db2 100644 --- a/gcc/testsuite/g++.dg/gomp/block-1.C +++ b/gcc/testsuite/g++.dg/gomp/block-1.C @@ -20,3 +20,6 @@ void foo() { ok1: break; } } } + +// { dg-message "error: invalid branch to/from an OpenMP structured block" "" { target *-*-* } 7 } +// { dg-message "error: invalid entry to OpenMP structured block" "" { target *-*-* } 9 } diff --git a/gcc/testsuite/g++.dg/gomp/block-2.C b/gcc/testsuite/g++.dg/gomp/block-2.C index 621a90d7bc4ec9caed2e24ada5d788922112c45d..17d98d845a567142024e1b35bd522ea41971a4e8 100644 --- a/gcc/testsuite/g++.dg/gomp/block-2.C +++ b/gcc/testsuite/g++.dg/gomp/block-2.C @@ -30,3 +30,6 @@ void foo() for (i = 0; i < 10; ++i) continue; } + +// { dg-message "error: invalid branch to/from an OpenMP structured block" "" { target *-*-* } 14 } +// { dg-message "error: invalid entry to OpenMP structured block" "" { target *-*-* } 16 } diff --git a/gcc/testsuite/g++.dg/gomp/block-3.C b/gcc/testsuite/g++.dg/gomp/block-3.C index 8e036e45364df84265b24b4f98328fefd28d3210..aeb0c7795a005075d3e833334724cd24c9d0e673 100644 --- a/gcc/testsuite/g++.dg/gomp/block-3.C +++ b/gcc/testsuite/g++.dg/gomp/block-3.C @@ -55,3 +55,7 @@ void foo() } } } + +// { dg-message "error: invalid branch to/from an OpenMP structured block" "" { target *-*-* } 21 } +// { dg-message "error: invalid branch to/from an OpenMP structured block" "" { target *-*-* } 26 } +// { dg-message "error: invalid entry to OpenMP structured block" "" { target *-*-* } 30 } diff --git a/gcc/testsuite/g++.dg/gomp/block-5.C b/gcc/testsuite/g++.dg/gomp/block-5.C index 67ed72c8daafeeb298ba501517d3915f83c8a2bd..391f8b660a60d8a3e490bd7b84ea29247739ce2a 100644 --- a/gcc/testsuite/g++.dg/gomp/block-5.C +++ b/gcc/testsuite/g++.dg/gomp/block-5.C @@ -13,3 +13,5 @@ void foo() return; // { dg-error "invalid exit" } } } + +// { dg-message "error: invalid branch to/from an OpenMP structured block" "" { target *-*-* } 7 } diff --git a/gcc/testsuite/g++.dg/rtti/crash4.C b/gcc/testsuite/g++.dg/rtti/crash4.C new file mode 100644 index 0000000000000000000000000000000000000000..49807e99f08f39eeba001dfd2eacb8c85e177b3f --- /dev/null +++ b/gcc/testsuite/g++.dg/rtti/crash4.C @@ -0,0 +1,16 @@ +/* { dg-do compile } */ +/* { dg-options "-O" } */ + +class ios_base { +public: + virtual ~ios_base(); +}; +template<typename _CharT> +class basic_ostream : virtual public ios_base { +public: + virtual ~basic_ostream() { } +}; +extern template class basic_ostream<char>; +template <typename _CharT> +class basic_ostringstream : public basic_ostream<_CharT> { }; +template class basic_ostringstream<char>; diff --git a/gcc/testsuite/g++.dg/torture/20090706-1.C b/gcc/testsuite/g++.dg/torture/20090706-1.C new file mode 100644 index 0000000000000000000000000000000000000000..43a59f0e682a417460cf804241f1e796f4f7a976 --- /dev/null +++ b/gcc/testsuite/g++.dg/torture/20090706-1.C @@ -0,0 +1,41 @@ +/* { dg-do compile } */ + +namespace std __attribute__ ((__visibility__ ("default"))) { + template<typename _Tp> class new_allocator { }; + template<typename _Tp> class allocator: public new_allocator<_Tp> { }; + template<typename _Tp, typename _Alloc> struct _Vector_base { }; + template<typename _Tp, typename _Alloc = std::allocator<_Tp> > + class vector : protected _Vector_base<_Tp, _Alloc> { }; +}; +template<int Dim> class Vector { }; +enum CenteringType { VertexType, EdgeType, FaceType, CellType }; +enum ContinuityType { XDim = 1, YDim = XDim << 1, ZDim = YDim << 1 }; +template <int Dim> class Centering { +public: + typedef Vector<Dim> Position; + typedef std::vector<Position> Positions; + Centering(const Positions &positions); + Positions positions_m; +}; +template <int Dim> class CanonicalCentering { + CanonicalCentering(); + template <class T> static T combine(const T &op1, const T &op2); + static Centering<Dim>*** centering_table_m; +}; +template <int Dim> CanonicalCentering<Dim>::CanonicalCentering() +{ + typename Centering<Dim>::Positions positions[Dim][2]; + enum { x = 0, y, z }; + int cont = 0; + if (Dim > 1) + { + centering_table_m[EdgeType][cont][YDim] = Centering<Dim>(positions[y][cont]); + centering_table_m[EdgeType][cont][XDim|YDim] = Centering<Dim>(combine(positions[x][cont], positions[y][cont])); + } + if (Dim > 2) + { + centering_table_m[EdgeType][cont][ZDim] = Centering<Dim>(positions[z][cont]); + centering_table_m[EdgeType][cont][XDim|ZDim] = Centering<Dim>(combine(positions[x][cont], positions[z][cont])); + } +} +template class CanonicalCentering<2>; diff --git a/gcc/testsuite/g++.dg/warn/unused-result1.C b/gcc/testsuite/g++.dg/warn/unused-result1.C index 1b9ef8af786bfe8f695335ad0cce7d95f48a389f..466c99e7d97b92620e5b7e3eae729e806d26c24b 100644 --- a/gcc/testsuite/g++.dg/warn/unused-result1.C +++ b/gcc/testsuite/g++.dg/warn/unused-result1.C @@ -6,5 +6,5 @@ public: }; class QString { QByteArray toLocal8Bit() const __attribute__ ((warn_unused_result)); - void fooWarnHere() const { toLocal8Bit(); } // { dg-warning "ignoring" } + void fooWarnHere() const { toLocal8Bit(); } // { dg-warning "ignoring" "" { xfail *-*-* } } }; diff --git a/gcc/testsuite/g++.old-deja/g++.jason/report.C b/gcc/testsuite/g++.old-deja/g++.jason/report.C index e1079cfb0aaf0a0d76af841aec0d01df3327adf3..b595662c22850b7bc27c9f4c0c39f28e9897f049 100644 --- a/gcc/testsuite/g++.old-deja/g++.jason/report.C +++ b/gcc/testsuite/g++.old-deja/g++.jason/report.C @@ -72,3 +72,6 @@ int darg (char X::*p) { undef3 (1); // { dg-error "" } implicit declaration } // { dg-warning "no return statement" } + +// { dg-message "warning: control reaches end of non-void function" "" { target *-*-* } 36 } +// { dg-message "warning: control reaches end of non-void function" "" { target *-*-* } 65 } diff --git a/gcc/testsuite/gcc.dg/declspec-10.c b/gcc/testsuite/gcc.dg/declspec-10.c index f938bf10e7af45aa3d6b756f739456f70a0dc7ba..ddc60646ab0623f30cb604e7345762b4e03b694b 100644 --- a/gcc/testsuite/gcc.dg/declspec-10.c +++ b/gcc/testsuite/gcc.dg/declspec-10.c @@ -43,3 +43,5 @@ void i (void) { auto void y (void) {} } /* { dg-warning "ISO C forbids nested fu /* { dg-warning "function definition declared 'auto'" "nested" { target *-*-* } 42 } */ inline int main (void) { return 0; } /* { dg-warning "cannot inline function 'main'" } */ + +/* { dg-message "error: register name not specified for 'y'" "" { target *-*-* } 19 } */ diff --git a/gcc/testsuite/gcc.dg/declspec-11.c b/gcc/testsuite/gcc.dg/declspec-11.c index c3fec469a81f721e1d7067192e14e2553a44d159..9dfe63f99e32985122b0c4e9fc030ed0aa609ab2 100644 --- a/gcc/testsuite/gcc.dg/declspec-11.c +++ b/gcc/testsuite/gcc.dg/declspec-11.c @@ -43,3 +43,5 @@ void i (void) { auto void y (void) {} } /* { dg-error "ISO C forbids nested func /* { dg-error "function definition declared 'auto'" "nested" { target *-*-* } 42 } */ inline int main (void) { return 0; } /* { dg-error "cannot inline function 'main'" } */ + +/* { dg-message "error: register name not specified for 'y'" "" { target *-*-* } 19 } */ diff --git a/gcc/testsuite/gcc.dg/declspec-9.c b/gcc/testsuite/gcc.dg/declspec-9.c index ece47c66fb14a622f4723083359db21075674cec..7766ed6a4b8beb03812b43961aa0002410a97bbc 100644 --- a/gcc/testsuite/gcc.dg/declspec-9.c +++ b/gcc/testsuite/gcc.dg/declspec-9.c @@ -17,7 +17,7 @@ void f6 (static int); /* { dg-error "storage class specified for unnamed paramet void f7 (typedef int); /* { dg-error "storage class specified for unnamed parameter" } */ auto int x; /* { dg-error "file-scope declaration of 'x' specifies 'auto'" } */ -register int y; +register int y; /* { dg-error "register name not specified for 'y'" } */ void h (void) { extern void x (void) {} } /* { dg-error "nested function 'x' declared 'extern'" } */ diff --git a/gcc/testsuite/gcc.dg/redecl-10.c b/gcc/testsuite/gcc.dg/redecl-10.c index 88d804e6cfd67f1e898a1444c71beebf9eee8c9d..525961e7e3a62c83d031629370457a3ea901f0ef 100644 --- a/gcc/testsuite/gcc.dg/redecl-10.c +++ b/gcc/testsuite/gcc.dg/redecl-10.c @@ -12,7 +12,7 @@ f (void) extern int w[] = { 1, 2 }; /* { dg-error "has both" } */ } -int x[]; +int x[]; /* { dg-warning "array 'x' assumed to have one element" } */ void g (void) { @@ -26,7 +26,7 @@ h (void) extern int y[] = { 6 }; /* { dg-error "has both" } */ } -int z[]; +int z[]; /* { dg-warning "array 'z' assumed to have one element" } */ void i (void) { diff --git a/gcc/testsuite/gcc.dg/redecl-17.c b/gcc/testsuite/gcc.dg/redecl-17.c new file mode 100644 index 0000000000000000000000000000000000000000..686ebc5897195e76a47877b00192394c3b60a47b --- /dev/null +++ b/gcc/testsuite/gcc.dg/redecl-17.c @@ -0,0 +1,10 @@ +/* { dg-do compile } */ + +void (*fp)(const int i); +void (*fp)(int i); + +void foo() +{ + (*fp)(0); +} + diff --git a/gcc/testsuite/gcc.target/i386/pr39082-1.c b/gcc/testsuite/gcc.target/i386/pr39082-1.c index 4c4e2547a88486b926ae0fb36b594fc2e60b564b..81b5bb66d2b897ad9c60cf363c0e1b4c9317da02 100644 --- a/gcc/testsuite/gcc.target/i386/pr39082-1.c +++ b/gcc/testsuite/gcc.target/i386/pr39082-1.c @@ -13,7 +13,7 @@ extern int bar1 (union un); extern union un bar2 (int); int -foo1 (union un u) /* { dg-message "note: The ABI of passing union with long double has changed in GCC 4.4" } */ +foo1 (union un u) { bar1 (u); return u.i; @@ -30,6 +30,6 @@ foo2 (void) int foo3 (int x) { - union un u = bar2 (x); + union un u = bar2 (x); /* { dg-message "note: The ABI of passing union with long double has changed in GCC 4.4" } */ return u.i; } diff --git a/gcc/testsuite/gcc.target/i386/pr39545-1.c b/gcc/testsuite/gcc.target/i386/pr39545-1.c index 62bc33fa21d59dc2c82576508e97ecc90b183481..281c8cbf369ef66789c8faea664ab527dcdbb57e 100644 --- a/gcc/testsuite/gcc.target/i386/pr39545-1.c +++ b/gcc/testsuite/gcc.target/i386/pr39545-1.c @@ -10,14 +10,14 @@ struct flex }; int -foo (struct flex s) /* { dg-message "note: The ABI of passing struct with a flexible array member has changed in GCC 4.4" } */ +foo (struct flex s) { return s.i; } struct flex bar (int x) -{ +{ /* { dg-message "note: The ABI of passing struct with a flexible array member has changed in GCC 4.4" } */ struct flex s; s.i = x; return s; diff --git a/gcc/testsuite/gfortran.dg/missing_optional_dummy_5.f90 b/gcc/testsuite/gfortran.dg/missing_optional_dummy_5.f90 index 4ad399e8a98cef94ec15ba707af72c73491eb6d8..29a9d70f899800c3b2e70ba54dd185d2f2eeca18 100644 --- a/gcc/testsuite/gfortran.dg/missing_optional_dummy_5.f90 +++ b/gcc/testsuite/gfortran.dg/missing_optional_dummy_5.f90 @@ -23,7 +23,7 @@ contains end function tm_doit end module krmod -! { dg-final { scan-tree-dump " tm_doit \\(&parm.\(6|7\), 0B, 0\\);" "original" } } +! { dg-final { scan-tree-dump " tm_doit \\(&parm\.., 0B, 0\\);" "original" } } ! { dg-final { cleanup-tree-dump "original" } } ! { dg-final { cleanup-modules "krmod" } } diff --git a/gcc/toplev.c b/gcc/toplev.c index 2bd392becc193e64541ae5d46bc78110d4d482d4..6fa3f1a44ec79194fcf25da508c7a6d2576b1a72 100644 --- a/gcc/toplev.c +++ b/gcc/toplev.c @@ -1034,6 +1034,8 @@ compile_file (void) ggc_protect_identifiers = false; + /* This must also call cgraph_finalize_compilation_unit and + cgraph_optimize. */ lang_hooks.decls.final_write_globals (); if (errorcount || sorrycount) diff --git a/gcc/tree-cfg.c b/gcc/tree-cfg.c index bd6940f6fa71c5c99ba5f0ea93709a422cd4fa04..964a537266fc7840634244015ae06dec5a5c67ae 100644 --- a/gcc/tree-cfg.c +++ b/gcc/tree-cfg.c @@ -7370,3 +7370,100 @@ struct gimple_opt_pass pass_warn_function_noreturn = 0 /* todo_flags_finish */ } }; + + +/* Walk a gimplified function and warn for functions whose return value is + ignored and attribute((warn_unused_result)) is set. This is done before + inlining, so we don't have to worry about that. */ + +static void +do_warn_unused_result (gimple_seq seq) +{ + tree fdecl, ftype; + gimple_stmt_iterator i; + + for (i = gsi_start (seq); !gsi_end_p (i); gsi_next (&i)) + { + gimple g = gsi_stmt (i); + + switch (gimple_code (g)) + { + case GIMPLE_BIND: + do_warn_unused_result (gimple_bind_body (g)); + break; + case GIMPLE_TRY: + do_warn_unused_result (gimple_try_eval (g)); + do_warn_unused_result (gimple_try_cleanup (g)); + break; + case GIMPLE_CATCH: + do_warn_unused_result (gimple_catch_handler (g)); + break; + case GIMPLE_EH_FILTER: + do_warn_unused_result (gimple_eh_filter_failure (g)); + break; + + case GIMPLE_CALL: + if (gimple_call_lhs (g)) + break; + + /* This is a naked call, as opposed to a GIMPLE_CALL with an + LHS. All calls whose value is ignored should be + represented like this. Look for the attribute. */ + fdecl = gimple_call_fndecl (g); + ftype = TREE_TYPE (TREE_TYPE (gimple_call_fn (g))); + + if (lookup_attribute ("warn_unused_result", TYPE_ATTRIBUTES (ftype))) + { + location_t loc = gimple_location (g); + + if (fdecl) + warning_at (loc, OPT_Wunused_result, + "ignoring return value of %qD, " + "declared with attribute warn_unused_result", + fdecl); + else + warning_at (loc, OPT_Wunused_result, + "ignoring return value of function " + "declared with attribute warn_unused_result"); + } + break; + + default: + /* Not a container, not a call, or a call whose value is used. */ + break; + } + } +} + +static unsigned int +run_warn_unused_result (void) +{ + do_warn_unused_result (gimple_body (current_function_decl)); + return 0; +} + +static bool +gate_warn_unused_result (void) +{ + return flag_warn_unused_result; +} + +struct gimple_opt_pass pass_warn_unused_result = +{ + { + GIMPLE_PASS, + "warn_unused_result", /* name */ + gate_warn_unused_result, /* gate */ + run_warn_unused_result, /* execute */ + NULL, /* sub */ + NULL, /* next */ + 0, /* static_pass_number */ + TV_NONE, /* tv_id */ + PROP_gimple_any, /* properties_required */ + 0, /* properties_provided */ + 0, /* properties_destroyed */ + 0, /* todo_flags_start */ + 0, /* todo_flags_finish */ + } +}; + diff --git a/gcc/tree-inline.c b/gcc/tree-inline.c index ed947da759a0ba20cfbe3bd7b76533aabc794eb5..a28f0a4cbbc9925f1e9cb5dc8ea84eaf720f777a 100644 --- a/gcc/tree-inline.c +++ b/gcc/tree-inline.c @@ -603,7 +603,12 @@ copy_statement_list (tree *tp) *tp = new_tree; for (; !tsi_end_p (oi); tsi_next (&oi)) - tsi_link_after (&ni, tsi_stmt (oi), TSI_NEW_STMT); + { + tree stmt = tsi_stmt (oi); + if (TREE_CODE (stmt) == STATEMENT_LIST) + copy_statement_list (&stmt); + tsi_link_after (&ni, stmt, TSI_CONTINUE_LINKING); + } } static void @@ -921,7 +926,8 @@ copy_tree_body_r (tree *tp, int *walk_subtrees, void *data) } else if (TREE_CODE (*tp) == STATEMENT_LIST) copy_statement_list (tp); - else if (TREE_CODE (*tp) == SAVE_EXPR) + else if (TREE_CODE (*tp) == SAVE_EXPR + || TREE_CODE (*tp) == TARGET_EXPR) remap_save_expr (tp, id->decl_map, walk_subtrees); else if (TREE_CODE (*tp) == LABEL_DECL && (! DECL_CONTEXT (*tp) @@ -3919,7 +3925,8 @@ unsave_r (tree *tp, int *walk_subtrees, void *data) gcc_unreachable (); else if (TREE_CODE (*tp) == BIND_EXPR) copy_bind_expr (tp, walk_subtrees, id); - else if (TREE_CODE (*tp) == SAVE_EXPR) + else if (TREE_CODE (*tp) == SAVE_EXPR + || TREE_CODE (*tp) == TARGET_EXPR) remap_save_expr (tp, st, walk_subtrees); else { diff --git a/gcc/tree-nested.c b/gcc/tree-nested.c index 80041ec66a7b248018ee4f866a914241da9fa127..7c55c8adc2346fa72edacbe2674a135444dc4801 100644 --- a/gcc/tree-nested.c +++ b/gcc/tree-nested.c @@ -2443,6 +2443,17 @@ free_nesting_tree (struct nesting_info *root) while (root); } +/* Gimplify a function and all its nested functions. */ +static void +gimplify_all_functions (struct cgraph_node *root) +{ + struct cgraph_node *iter; + if (!gimple_body (root->decl)) + gimplify_function_tree (root->decl); + for (iter = root->nested; iter; iter = iter->next_nested) + gimplify_all_functions (iter); +} + /* Main entry point for this pass. Process FNDECL and all of its nested subroutines and turn them into something less tightly bound. */ @@ -2457,6 +2468,8 @@ lower_nested_functions (tree fndecl) if (!cgn->nested) return; + gimplify_all_functions (cgn); + bitmap_obstack_initialize (&nesting_info_bitmap_obstack); root = create_nesting_tree (cgn); walk_all_functions (convert_nonlocal_reference_stmt, diff --git a/gcc/tree-pass.h b/gcc/tree-pass.h index db3ebce28cc93a1239b6a1699429bf8750f9252a..a68cb16350b2d5ff48eedf984b3368aa2775e662 100644 --- a/gcc/tree-pass.h +++ b/gcc/tree-pass.h @@ -279,10 +279,6 @@ struct dump_file_info and the memory footprint for VAR_DECLs. */ #define TODO_remove_unused_locals (1 << 15) -/* Internally used for the first in a sequence of passes. It is set - for the passes that are handed to register_dump_files. */ -#define TODO_set_props (1 << 16) - /* Call df_finish at the end of the pass. This is done after all of the dumpers have been allowed to run so that they have access to the instance before it is destroyed. */ @@ -370,6 +366,7 @@ extern struct gimple_opt_pass pass_lower_complex; extern struct gimple_opt_pass pass_lower_vector; extern struct gimple_opt_pass pass_lower_vector_ssa; extern struct gimple_opt_pass pass_lower_omp; +extern struct gimple_opt_pass pass_diagnose_omp_blocks; extern struct gimple_opt_pass pass_expand_omp; extern struct gimple_opt_pass pass_expand_omp_ssa; extern struct gimple_opt_pass pass_object_sizes; @@ -406,6 +403,7 @@ extern struct gimple_opt_pass pass_remove_cgraph_callee_edges; extern struct gimple_opt_pass pass_build_cgraph_edges; extern struct gimple_opt_pass pass_local_pure_const; extern struct gimple_opt_pass pass_tracer; +extern struct gimple_opt_pass pass_warn_unused_result; /* IPA Passes */ extern struct ipa_opt_pass_d pass_ipa_inline;