Hi, Whereas the previous patch fixed issues with code left behind after IPA-SRA removed a parameter but only reset all affected debug bind statements, this one updates them with expressions which can allow the debugger to print the removed value - see the added test-case.
Even though I originally did not want to create DEBUG_EXPR_DECLs for intermediate values, I ended up doing so, because otherwise the code started creating statements like # DEBUG __aD.198693 => &MEM[(const struct _Alloc_nodeD.171110 *)D#195]._M_tD.184726->_M_implD.171154 which not only is a bit scary but also gimple-fold ICEs on it. Therefore I decided they are probably quite necessary and have them. The patch simply notes each removed SSA name present in a debug statement and then works from it backwards, looking if it can reconstruct the expression it represents (which can fail if a non-degenerate PHI node is in the way). If it can, it populates two hash maps with those expressions so that 1) removed assignments are replaced with a debug bind defining a new intermediate debug_decl_expr and 2) existing debug binds that refer to SSA names that are bing removed now refer to corresponding debug_decl_exprs. If a removed parameter is passed to another function, the debugging information still cannot describe its value there - see the xfailed test in the testcase. I sort of know what needs to be done but the handling of debug information for removed parameters is LTO unfriendly in general and so needs a bit more work. Bootstrapped and tested on x86_64-linux, i686-linux and aarch64-linux. Also LTO-bootstrapped and LTO-profiledbootstrapped on x86_64-linux. OK for trunk? Thanks, Martin gcc/ChangeLog: 2021-03-29 Martin Jambor <mjam...@suse.cz> PR ipa/93385 * ipa-param-manipulation.h (class ipa_param_body_adjustments): New members remap_with_debug_expressions, m_dead_ssa_debug_equiv, m_dead_stmt_debug_equiv and prepare_debug_expressions. Added parameter to mark_dead_statements. * ipa-param-manipulation.c: Include tree-phinodes.h and cfgexpand.h. (ipa_param_body_adjustments::mark_dead_statements): New parameter debugstack, push into it all SSA names used in debug statements, produce m_dead_ssa_debug_equiv mapping for the removed param. (replace_with_mapped_expr): New function. (ipa_param_body_adjustments::remap_with_debug_expressions): Likewise. (ipa_param_body_adjustments::prepare_debug_expressions): Likewise. (ipa_param_body_adjustments::common_initialization): Gather and procecc SSA which will be removed but are in debug statements. Simplify. (ipa_param_body_adjustments::ipa_param_body_adjustments): Initialize new members. * tree-inline.c (remap_gimple_stmt): Create a debug bind when possible when avoiding a copy of an unnecessary statement. Remap removed SSA names in existing debug statements. (tree_function_versioning): Do not create DEBUG_EXPR_DECL for removed parameters if we have already done so. gcc/testsuite/ChangeLog: 2021-03-29 Martin Jambor <mjam...@suse.cz> PR ipa/93385 * gcc.dg/guality/ipa-sra-1.c: New test. --- gcc/ipa-param-manipulation.c | 281 ++++++++++++++++++----- gcc/ipa-param-manipulation.h | 12 +- gcc/testsuite/gcc.dg/guality/ipa-sra-1.c | 45 ++++ gcc/tree-inline.c | 45 ++-- 4 files changed, 306 insertions(+), 77 deletions(-) create mode 100644 gcc/testsuite/gcc.dg/guality/ipa-sra-1.c diff --git a/gcc/ipa-param-manipulation.c b/gcc/ipa-param-manipulation.c index 3e07fd72fe2..a202501fc95 100644 --- a/gcc/ipa-param-manipulation.c +++ b/gcc/ipa-param-manipulation.c @@ -43,6 +43,8 @@ along with GCC; see the file COPYING3. If not see #include "alloc-pool.h" #include "symbol-summary.h" #include "symtab-clones.h" +#include "tree-phinodes.h" +#include "cfgexpand.h" /* Actual prefixes of different newly synthetized parameters. Keep in sync @@ -989,10 +991,12 @@ phi_arg_will_live_p (gphi *phi, bitmap blocks_to_copy, tree arg) /* Populate m_dead_stmts given that DEAD_PARAM is going to be removed without any replacement or splitting. REPL is the replacement VAR_SECL to base any - remaining uses of a removed parameter on. */ + remaining uses of a removed parameter on. Push all removed SSA names that + are used within debug statements to DEBUGSTACK. */ void -ipa_param_body_adjustments::mark_dead_statements (tree dead_param) +ipa_param_body_adjustments::mark_dead_statements (tree dead_param, + vec<tree> *debugstack) { /* Current IPA analyses which remove unused parameters never remove a non-gimple register ones which have any use except as parameters in other @@ -1004,6 +1008,7 @@ ipa_param_body_adjustments::mark_dead_statements (tree dead_param) return; auto_vec<tree, 4> stack; + hash_set<tree> used_in_debug; m_dead_ssas.add (parm_ddef); stack.safe_push (parm_ddef); while (!stack.is_empty ()) @@ -1026,6 +1031,11 @@ ipa_param_body_adjustments::mark_dead_statements (tree dead_param) { m_dead_stmts.add (stmt); gcc_assert (gimple_debug_bind_p (stmt)); + if (!used_in_debug.contains (t)) + { + used_in_debug.add (t); + debugstack->safe_push (t); + } } else if (gimple_code (stmt) == GIMPLE_PHI) { @@ -1054,6 +1064,149 @@ ipa_param_body_adjustments::mark_dead_statements (tree dead_param) gcc_unreachable (); } } + + if (!MAY_HAVE_DEBUG_STMTS) + { + gcc_assert (debugstack->is_empty ()); + return; + } + + tree dp_ddecl = make_node (DEBUG_EXPR_DECL); + DECL_ARTIFICIAL (dp_ddecl) = 1; + TREE_TYPE (dp_ddecl) = TREE_TYPE (dead_param); + SET_DECL_MODE (dp_ddecl, DECL_MODE (dead_param)); + m_dead_ssa_debug_equiv.put (parm_ddef, dp_ddecl); +} + +/* Callback to walk_tree. If REMAP is an SSA_NAME that is present in hash_map + passed in DATA, replace it with unshared version of what it was mapped + to. */ + +static tree +replace_with_mapped_expr (tree *remap, int *walk_subtrees, void *data) +{ + if (TYPE_P (*remap)) + { + *walk_subtrees = 0; + return 0; + } + if (TREE_CODE (*remap) != SSA_NAME) + return 0; + + *walk_subtrees = 0; + + hash_map<tree, tree> *equivs = (hash_map<tree, tree> *) data; + if (tree *p = equivs->get (*remap)) + *remap = unshare_expr (*p); + return 0; +} + +/* Replace all occurances of SSAs in m_dead_ssa_debug_equiv in t with what they + are mapped to. */ + +void +ipa_param_body_adjustments::remap_with_debug_expressions (tree *t) +{ + /* If *t is an SSA_NAME which should have its debug statements reset, it is + mapped to NULL in the hash_map. We need to handle that case separately or + otherwise the walker would segfault. No expression that is more + complicated than that can have its operands mapped to NULL. */ + if (TREE_CODE (*t) == SSA_NAME) + { + if (tree *p = m_dead_ssa_debug_equiv.get (*t)) + *t = *p; + } + else + walk_tree (t, replace_with_mapped_expr, &m_dead_ssa_debug_equiv, NULL); +} + +/* For an SSA_NAME DEAD_SSA which is about to be DCEd because it is based on a + useless parameter, prepare an expression that should represent it in + debug_binds in the cloned function and add a mapping from DEAD_SSA to + m_dead_ssa_debug_equiv. That mapping is to NULL when the associated + debug_statement has to be reset instead. In such case return false, + ottherwise return true. If DEAD_SSA comes from a basic block which is not + about to be copied, ignore it and return true. */ + +bool +ipa_param_body_adjustments::prepare_debug_expressions (tree dead_ssa) +{ + gcc_checking_assert (m_dead_ssas.contains (dead_ssa)); + if (tree *d = m_dead_ssa_debug_equiv.get (dead_ssa)) + return (*d != NULL_TREE); + + gcc_assert (!SSA_NAME_IS_DEFAULT_DEF (dead_ssa)); + gimple *def = SSA_NAME_DEF_STMT (dead_ssa); + if (m_id->blocks_to_copy + && !bitmap_bit_p (m_id->blocks_to_copy, gimple_bb (def)->index)) + return true; + + if (gimple_code (def) == GIMPLE_PHI) + { + /* In theory, we could ignore all SSAs coming from BBs not in + m_id->blocks_to_copy but at the time of the writing this code that + should never really be the case because only fnsplit uses that bitmap, + so don't bother. */ + tree value = degenerate_phi_result (as_a <gphi *> (def)); + if (!value + || (m_dead_ssas.contains (value) + && !prepare_debug_expressions (value))) + { + m_dead_ssa_debug_equiv.put (dead_ssa, NULL_TREE); + return false; + } + + gcc_assert (TREE_CODE (value) == SSA_NAME); + tree *d = m_dead_ssa_debug_equiv.get (value); + m_dead_ssa_debug_equiv.put (dead_ssa, *d); + return true; + } + + bool lost = false; + use_operand_p use_p; + ssa_op_iter oi; + FOR_EACH_PHI_OR_STMT_USE (use_p, def, oi, SSA_OP_USE) + { + tree use = USE_FROM_PTR (use_p); + if (m_dead_ssas.contains (use) + && !prepare_debug_expressions (use)) + { + lost = true; + break; + } + } + + if (lost) + { + m_dead_ssa_debug_equiv.put (dead_ssa, NULL_TREE); + return false; + } + + if (is_gimple_assign (def)) + { + gcc_assert (!gimple_clobber_p (def)); + if (gimple_assign_copy_p (def) + && TREE_CODE (gimple_assign_rhs1 (def)) == SSA_NAME) + { + tree *d = m_dead_ssa_debug_equiv.get (gimple_assign_rhs1 (def)); + m_dead_ssa_debug_equiv.put (dead_ssa, *d); + return (*d != NULL_TREE); + } + + tree val = gimple_assign_rhs_to_tree (def); + SET_EXPR_LOCATION (val, UNKNOWN_LOCATION); + remap_with_debug_expressions (&val); + + tree vexpr = make_node (DEBUG_EXPR_DECL); + DECL_ARTIFICIAL (vexpr) = 1; + TREE_TYPE (vexpr) = TREE_TYPE (val); + SET_DECL_MODE (vexpr, TYPE_MODE (TREE_TYPE (val))); + m_dead_stmt_debug_equiv.put (def, val); + m_dead_ssa_debug_equiv.put (dead_ssa, vexpr); + return true; + } + else + gcc_unreachable (); } /* Common initialization performed by all ipa_param_body_adjustments @@ -1145,65 +1298,21 @@ ipa_param_body_adjustments::common_initialization (tree old_fndecl, gcc_unreachable (); } - - /* As part of body modifications, we will also have to replace remaining uses - of remaining uses of removed PARM_DECLs (which do not however use the - initial value) with their VAR_DECL copies. - - We do this differently with and without m_id. With m_id, we rely on its - mapping and create a replacement straight away. Without it, we have our - own mechanism for which we have to populate m_removed_decls vector. Just - don't mix them, that is why you should not call - replace_removed_params_ssa_names or perform_cfun_body_modifications when - you construct with ID not equal to NULL. */ - - unsigned op_len = m_oparms.length (); - for (unsigned i = 0; i < op_len; i++) - if (!kept[i]) - { - if (m_id) - { - if (!m_id->decl_map->get (m_oparms[i])) - { - tree var = copy_decl_to_var (m_oparms[i], m_id); - insert_decl_map (m_id, m_oparms[i], var); - /* Declare this new variable. */ - DECL_CHAIN (var) = *vars; - *vars = var; - - /* If this is not a split but a real removal, init hash sets - that will guide what not to copy to the new body. */ - if (!split[i]) - mark_dead_statements (m_oparms[i]); - } - } - else - { - m_removed_decls.safe_push (m_oparms[i]); - m_removed_map.put (m_oparms[i], m_removed_decls.length () - 1); - } - } - - if (!MAY_HAVE_DEBUG_STMTS) - return; - - /* Finally, when generating debug info, we fill vector m_reset_debug_decls - with removed parameters declarations. We do this in order to re-map their - debug bind statements and create debug decls for them. */ - if (tree_map) { - /* Do not output debuginfo for parameter declarations as if they vanished - when they were in fact replaced by a constant. */ + /* Do not treat parameters which were replaced with a constant as + completely vanished. */ auto_vec <int, 16> index_mapping; bool need_remap = false; - clone_info *info = clone_info::get (m_id->src_node); - if (m_id && info && info->param_adjustments) + if (m_id) { - ipa_param_adjustments *prev_adjustments = info->param_adjustments; - prev_adjustments->get_updated_indices (&index_mapping); - need_remap = true; + clone_info *cinfo = clone_info::get (m_id->src_node); + if (cinfo && cinfo->param_adjustments) + { + cinfo->param_adjustments->get_updated_indices (&index_mapping); + need_remap = true; + } } for (unsigned i = 0; i < tree_map->length (); i++) @@ -1216,9 +1325,52 @@ ipa_param_body_adjustments::common_initialization (tree old_fndecl, } } + /* As part of body modifications, we will also have to replace remaining uses + of remaining uses of removed PARM_DECLs (which do not however use the + initial value) with their VAR_DECL copies. + + We do this differently with and without m_id. With m_id, we rely on its + mapping and create a replacement straight away. Without it, we have our + own mechanism for which we have to populate m_removed_decls vector. Just + don't mix them, that is why you should not call + replace_removed_params_ssa_names or perform_cfun_body_modifications when + you construct with ID not equal to NULL. */ + + auto_vec<tree, 8> ssas_to_process_debug; + unsigned op_len = m_oparms.length (); for (unsigned i = 0; i < op_len; i++) - if (!kept[i] && is_gimple_reg (m_oparms[i])) - m_reset_debug_decls.safe_push (m_oparms[i]); + if (!kept[i]) + { + if (m_id) + { + gcc_assert (!m_id->decl_map->get (m_oparms[i])); + tree var = copy_decl_to_var (m_oparms[i], m_id); + insert_decl_map (m_id, m_oparms[i], var); + /* Declare this new variable. */ + DECL_CHAIN (var) = *vars; + *vars = var; + + /* If this is not a split but a real removal, init hash sets + that will guide what not to copy to the new body. */ + if (!split[i]) + mark_dead_statements (m_oparms[i], &ssas_to_process_debug); + if (MAY_HAVE_DEBUG_STMTS + && is_gimple_reg (m_oparms[i])) + m_reset_debug_decls.safe_push (m_oparms[i]); + } + else + { + m_removed_decls.safe_push (m_oparms[i]); + m_removed_map.put (m_oparms[i], m_removed_decls.length () - 1); + if (MAY_HAVE_DEBUG_STMTS + && !kept[i] + && is_gimple_reg (m_oparms[i])) + m_reset_debug_decls.safe_push (m_oparms[i]); + } + } + + while (!ssas_to_process_debug.is_empty ()) + prepare_debug_expressions (ssas_to_process_debug.pop ()); } /* Constructor of ipa_param_body_adjustments from a simple list of @@ -1232,9 +1384,10 @@ ipa_param_body_adjustments tree fndecl) : m_adj_params (adj_params), m_adjustments (NULL), m_reset_debug_decls (), m_split_modifications_p (false), m_dead_stmts (), m_dead_ssas (), - m_fndecl (fndecl), m_id (NULL), m_oparms (), m_new_decls (), - m_new_types (), m_replacements (), m_removed_decls (), m_removed_map (), - m_method2func (false), m_new_call_arg_modification_info (false) + m_dead_ssa_debug_equiv (), m_dead_stmt_debug_equiv (), m_fndecl (fndecl), + m_id (NULL), m_oparms (), m_new_decls (), m_new_types (), m_replacements (), + m_removed_decls (), m_removed_map (), m_method2func (false), + m_new_call_arg_modification_info (false) { common_initialization (fndecl, NULL, NULL); } @@ -1249,7 +1402,8 @@ ipa_param_body_adjustments tree fndecl) : m_adj_params (adjustments->m_adj_params), m_adjustments (adjustments), m_reset_debug_decls (), m_split_modifications_p (false), m_dead_stmts (), - m_dead_ssas (), m_fndecl (fndecl), m_id (NULL), m_oparms (), m_new_decls (), + m_dead_ssas (), m_dead_ssa_debug_equiv (), m_dead_stmt_debug_equiv (), + m_fndecl (fndecl), m_id (NULL), m_oparms (), m_new_decls (), m_new_types (), m_replacements (), m_removed_decls (), m_removed_map (), m_method2func (false), m_new_call_arg_modification_info (false) { @@ -1272,8 +1426,9 @@ ipa_param_body_adjustments vec<ipa_replace_map *, va_gc> *tree_map) : m_adj_params (adjustments->m_adj_params), m_adjustments (adjustments), m_reset_debug_decls (), m_split_modifications_p (false), m_dead_stmts (), - m_dead_ssas (),m_fndecl (fndecl), m_id (id), m_oparms (), m_new_decls (), - m_new_types (), m_replacements (), m_removed_decls (), m_removed_map (), + m_dead_ssas (), m_dead_ssa_debug_equiv (), m_dead_stmt_debug_equiv (), + m_fndecl (fndecl), m_id (id), m_oparms (), m_new_decls (), m_new_types (), + m_replacements (), m_removed_decls (), m_removed_map (), m_method2func (false), m_new_call_arg_modification_info (false) { common_initialization (old_fndecl, vars, tree_map); diff --git a/gcc/ipa-param-manipulation.h b/gcc/ipa-param-manipulation.h index f59d17717ee..fa05859f1f3 100644 --- a/gcc/ipa-param-manipulation.h +++ b/gcc/ipa-param-manipulation.h @@ -328,6 +328,9 @@ public: gimple *orig_stmt); /* Return the new chain of parameters. */ tree get_new_param_chain (); + /* Replace all occurances of SSAs in m_dead_ssa_debug_equiv in t with what + they are mapped to. */ + void remap_with_debug_expressions (tree *t); /* Pointers to data structures defining how the function should be modified. */ @@ -348,6 +351,12 @@ public: hash_set<gimple *> m_dead_stmts; hash_set<tree> m_dead_ssas; + /* Mapping from DCEd SSAs to what their potential debug_binds should be. */ + hash_map<tree, tree> m_dead_ssa_debug_equiv; + /* Mapping from DCEd statements to debug expressions that will be placed on + the RHS of debug statement that will replace this one. */ + hash_map<gimple *, tree> m_dead_stmt_debug_equiv; + private: void common_initialization (tree old_fndecl, tree *vars, vec<ipa_replace_map *, va_gc> *tree_map); @@ -361,7 +370,8 @@ private: bool modify_call_stmt (gcall **stmt_p, gimple *orig_stmt); bool modify_cfun_body (); void reset_debug_stmts (); - void mark_dead_statements (tree dead_param); + void mark_dead_statements (tree dead_param, vec<tree> *debugstack); + bool prepare_debug_expressions (tree dead_ssa); /* Declaration of the function that is being transformed. */ diff --git a/gcc/testsuite/gcc.dg/guality/ipa-sra-1.c b/gcc/testsuite/gcc.dg/guality/ipa-sra-1.c new file mode 100644 index 00000000000..5434b3d7665 --- /dev/null +++ b/gcc/testsuite/gcc.dg/guality/ipa-sra-1.c @@ -0,0 +1,45 @@ +/* { dg-do run } */ +/* { dg-options "-g -fno-ipa-icf" } */ + + +void __attribute__((noipa)) +use (int x) +{ + asm volatile ("" : : "r" (x) : "memory"); +} + +static int __attribute__((noinline)) +bar (int i, int k) +{ + asm ("" : "+r" (i)); + use (i); /* { dg-final { gdb-test . "k" "3" { xfail *-*-* } } } */ + return 6; +} + +volatile int v; + +static int __attribute__((noinline)) +foo (int i, int k) +{ + int r; + v = 9; + k = (k + 14)/k; + r = bar (i, k); /* { dg-final { gdb-test . "k" "3" } } */ + return r; +} + +volatile int v; + +int __attribute__((noipa)) +get_val1 (void) {return 20;} +int __attribute__((noipa)) +get_val2 (void) {return 7;} + +int +main (void) +{ + int k = get_val2 (); + int r = foo (get_val1 (), k); + v = r + k; /* k has to live accross the call or all is probably lost */ + return 0; +} diff --git a/gcc/tree-inline.c b/gcc/tree-inline.c index 165c4ad7c72..0a480e9b0e6 100644 --- a/gcc/tree-inline.c +++ b/gcc/tree-inline.c @@ -1531,7 +1531,21 @@ remap_gimple_stmt (gimple *stmt, copy_body_data *id) if (!is_gimple_debug (stmt) && id->param_body_adjs && id->param_body_adjs->m_dead_stmts.contains (stmt)) - return NULL; + { + tree *dval = id->param_body_adjs->m_dead_stmt_debug_equiv.get (stmt); + if (!dval) + return NULL; + + gcc_assert (is_gimple_assign (stmt)); + tree lhs = gimple_assign_lhs (stmt); + tree *dvar = id->param_body_adjs->m_dead_ssa_debug_equiv.get (lhs); + gdebug *bind = gimple_build_debug_bind (*dvar, *dval, stmt); + if (id->reset_location) + gimple_set_location (bind, input_location); + id->debug_stmts.safe_push (bind); + gimple_seq_add_stmt (&stmts, bind); + return stmts; + } /* Begin by recognizing trees that we'll completely rewrite for the inlining context. Our output for these trees is completely @@ -1797,15 +1811,13 @@ remap_gimple_stmt (gimple *stmt, copy_body_data *id) if (gimple_debug_bind_p (stmt)) { - tree value; + tree var = gimple_debug_bind_get_var (stmt); + tree value = gimple_debug_bind_get_value (stmt); if (id->param_body_adjs && id->param_body_adjs->m_dead_stmts.contains (stmt)) - value = NULL_TREE; - else - value = gimple_debug_bind_get_value (stmt); - gdebug *copy - = gimple_build_debug_bind (gimple_debug_bind_get_var (stmt), - value, stmt); + id->param_body_adjs->remap_with_debug_expressions (&value); + + gdebug *copy = gimple_build_debug_bind (var, value, stmt); if (id->reset_location) gimple_set_location (copy, input_location); id->debug_stmts.safe_push (copy); @@ -6431,7 +6443,6 @@ tree_function_versioning (tree old_decl, tree new_decl, in the debug info that var (whole DECL_ORIGIN is the parm PARM_DECL) is optimized away, but could be looked up at the call site as value of D#X there. */ - tree vexpr; gimple_stmt_iterator cgsi = gsi_after_labels (single_succ (ENTRY_BLOCK_PTR_FOR_FN (cfun))); gimple *def_temp; @@ -6439,17 +6450,25 @@ tree_function_versioning (tree old_decl, tree new_decl, i = vec_safe_length (*debug_args); do { + tree vexpr = NULL_TREE; i -= 2; while (var != NULL_TREE && DECL_ABSTRACT_ORIGIN (var) != (**debug_args)[i]) var = TREE_CHAIN (var); if (var == NULL_TREE) break; - vexpr = make_node (DEBUG_EXPR_DECL); tree parm = (**debug_args)[i]; - DECL_ARTIFICIAL (vexpr) = 1; - TREE_TYPE (vexpr) = TREE_TYPE (parm); - SET_DECL_MODE (vexpr, DECL_MODE (parm)); + if (tree parm_ddef = ssa_default_def (id.src_cfun, parm)) + if (tree *d + = param_body_adjs->m_dead_ssa_debug_equiv.get (parm_ddef)) + vexpr = *d; + if (!vexpr) + { + vexpr = make_node (DEBUG_EXPR_DECL); + DECL_ARTIFICIAL (vexpr) = 1; + TREE_TYPE (vexpr) = TREE_TYPE (parm); + SET_DECL_MODE (vexpr, DECL_MODE (parm)); + } def_temp = gimple_build_debug_bind (var, vexpr, NULL); gsi_insert_before (&cgsi, def_temp, GSI_NEW_STMT); def_temp = gimple_build_debug_source_bind (vexpr, parm, NULL); -- 2.31.1