From a513fe886b1dba3d2c9ed39fd633c35de45ddd4b Mon Sep 17 00:00:00 2001 From: Jeff Law <law@redhat.com> Date: Mon, 13 Jun 2005 17:24:47 -0600 Subject: [PATCH] tree-ssa-dom.c (simplify_rhs_and_lookup_avail_expr): No longer simplify DIV, MOD or ABS expressions using VRP information. * tree-ssa-dom.c (simplify_rhs_and_lookup_avail_expr): No longer simplify DIV, MOD or ABS expressions using VRP information. Remove WALK_DATA parameter. Prototype and all callers updated. (eliminate_redundant_computations): Remove WALK_DATA parameter. Prototype and all callers updated. (optimize_stmt): WALK_DATA parameter is now unused. * tree-vrp.c (local_fold): New function. Like fold, but strips useless type conversions in the result. (simplify_using_ranges): New function, largely cribbed from tree-ssa-dom.c::simplify_rhs_and_lookup_avail_expr. (vrp_finalize): Call simplify_using_ranges. * gcc.dg/tree-ssa/20030807-10.c: VRP is now expected to perform the desired transformations. * gcc.dg/tree-ssa/20030806-6.c: Similarly. * gcc.dg/tree-ssa/20040514-2.c: Similarly. From-SVN: r100909 --- gcc/ChangeLog | 15 +++ gcc/testsuite/ChangeLog | 7 + gcc/testsuite/gcc.dg/tree-ssa/20030807-10.c | 8 +- gcc/testsuite/gcc.dg/tree-ssa/20030807-6.c | 14 +- gcc/testsuite/gcc.dg/tree-ssa/20040514-2.c | 7 +- gcc/tree-ssa-dom.c | 141 ++------------------ gcc/tree-vrp.c | 139 +++++++++++++++++++ 7 files changed, 183 insertions(+), 148 deletions(-) diff --git a/gcc/ChangeLog b/gcc/ChangeLog index 5aeb13036344..ee9433529e12 100644 --- a/gcc/ChangeLog +++ b/gcc/ChangeLog @@ -1,3 +1,18 @@ +2005-06-13 Jeff Law <law@redhat.com> + + * tree-ssa-dom.c (simplify_rhs_and_lookup_avail_expr): No longer + simplify DIV, MOD or ABS expressions using VRP information. + Remove WALK_DATA parameter. Prototype and all callers updated. + (eliminate_redundant_computations): Remove WALK_DATA parameter. + Prototype and all callers updated. + (optimize_stmt): WALK_DATA parameter is now unused. + + * tree-vrp.c (local_fold): New function. Like fold, but + strips useless type conversions in the result. + (simplify_using_ranges): New function, largely cribbed from + tree-ssa-dom.c::simplify_rhs_and_lookup_avail_expr. + (vrp_finalize): Call simplify_using_ranges. + 2005-06-13 Mark Mitchell <mark@codesourcery.com> * config/i386/x86-64.h (ASM_SPEC): Explicitly pass --64 to the diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog index a0c560f4a008..1b5d552341b8 100644 --- a/gcc/testsuite/ChangeLog +++ b/gcc/testsuite/ChangeLog @@ -1,3 +1,10 @@ +2005-06-13 Jeff Law <law@redhat.com> + + * gcc.dg/tree-ssa/20030807-10.c: VRP is now expected to + perform the desired transformations. + * gcc.dg/tree-ssa/20030806-6.c: Similarly. + * gcc.dg/tree-ssa/20040514-2.c: Similarly. + 2005-06-13 Tobias Schl"uter <tobias.schlueter@physik.uni-muenchen.de> PR fortran/22038 diff --git a/gcc/testsuite/gcc.dg/tree-ssa/20030807-10.c b/gcc/testsuite/gcc.dg/tree-ssa/20030807-10.c index 5865543a5a6b..a7c98bf886a2 100644 --- a/gcc/testsuite/gcc.dg/tree-ssa/20030807-10.c +++ b/gcc/testsuite/gcc.dg/tree-ssa/20030807-10.c @@ -1,5 +1,5 @@ /* { dg-do compile } */ -/* { dg-options "-O1 -fdump-tree-dom3" } */ +/* { dg-options "-O2 -fdump-tree-vrp" } */ extern const unsigned char mode_size[]; @@ -18,9 +18,9 @@ subreg_highpart_offset (outermode, innermode) } /* There should be one mask with the value 3. */ -/* { dg-final { scan-tree-dump-times " \& 3" 1 "dom3"} } */ +/* { dg-final { scan-tree-dump-times " \& 3" 1 "vrp"} } */ /* There should be one right shift by 2 places. */ -/* { dg-final { scan-tree-dump-times " >> 2" 1 "dom3"} } */ +/* { dg-final { scan-tree-dump-times " >> 2" 1 "vrp"} } */ -/* { dg-final { cleanup-tree-dump "dom3" } } */ +/* { dg-final { cleanup-tree-dump "vrp" } } */ diff --git a/gcc/testsuite/gcc.dg/tree-ssa/20030807-6.c b/gcc/testsuite/gcc.dg/tree-ssa/20030807-6.c index e01c43876a0d..12a623adcb65 100644 --- a/gcc/testsuite/gcc.dg/tree-ssa/20030807-6.c +++ b/gcc/testsuite/gcc.dg/tree-ssa/20030807-6.c @@ -1,8 +1,8 @@ /* { dg-do compile } */ -/* { dg-options "-O1 -fdump-tree-dom3" } */ +/* { dg-options "-O2 -fdump-tree-vrp" } */ -static void +void foo (distance, i, j) int distance[13][13]; int i, j; @@ -11,7 +11,7 @@ foo (distance, i, j) distance[i][0] = ((distance[i][j]) < 0 ? -(distance[i][j]) : (distance[i][j])); } -static void +void foo2 (distance, i, j) int distance[13][13]; int i, j; @@ -20,7 +20,7 @@ foo2 (distance, i, j) distance[i][0] = ((distance[i][j]) < 0 ? -(distance[i][j]) : (distance[i][j])); } -static void +void foo3 (distance, i, j) int distance[13][13]; int i, j; @@ -29,7 +29,7 @@ foo3 (distance, i, j) distance[i][0] = ((distance[i][j]) < 0 ? -(distance[i][j]) : (distance[i][j])); } -static void +void foo4 (distance, i, j) double distance[13][13]; int i, j; @@ -39,5 +39,5 @@ foo4 (distance, i, j) } /* There should be no ABS_EXPR. */ -/* { dg-final { scan-tree-dump-times "ABS_EXPR " 0 "dom3"} } */ -/* { dg-final { cleanup-tree-dump "dom3" } } */ +/* { dg-final { scan-tree-dump-times "ABS_EXPR " 0 "vrp"} } */ +/* { dg-final { cleanup-tree-dump "vrp" } } */ diff --git a/gcc/testsuite/gcc.dg/tree-ssa/20040514-2.c b/gcc/testsuite/gcc.dg/tree-ssa/20040514-2.c index 98cf3a283bae..11f766716040 100644 --- a/gcc/testsuite/gcc.dg/tree-ssa/20040514-2.c +++ b/gcc/testsuite/gcc.dg/tree-ssa/20040514-2.c @@ -1,5 +1,5 @@ /* { dg-do compile } */ -/* { dg-options "-O1 -fdump-tree-dom3" } */ +/* { dg-options "-O2 -fdump-tree-phiopt1" } */ int foo2 (distance, i, j) int distance; @@ -12,7 +12,6 @@ foo2 (distance, i, j) } /* There should be one ABS_EXPR and no conditionals. */ -/* { dg-final { scan-tree-dump-times "ABS_EXPR " 1 "dom3"} } */ -/* { dg-final { scan-tree-dump-times "if " 0 "dom3"} } */ +/* { dg-final { scan-tree-dump-times "ABS_EXPR " 1 "phiopt1"} } */ +/* { dg-final { scan-tree-dump-times "if " 0 "phiopt1"} } */ -/* { dg-final { cleanup-tree-dump "dom3" } } */ diff --git a/gcc/tree-ssa-dom.c b/gcc/tree-ssa-dom.c index 2bd527a231eb..03365619ed99 100644 --- a/gcc/tree-ssa-dom.c +++ b/gcc/tree-ssa-dom.c @@ -272,8 +272,7 @@ static void record_cond (tree, tree); static void record_const_or_copy (tree, tree); static void record_equality (tree, tree); static tree update_rhs_and_lookup_avail_expr (tree, tree, bool); -static tree simplify_rhs_and_lookup_avail_expr (struct dom_walk_data *, - tree, int); +static tree simplify_rhs_and_lookup_avail_expr (tree, int); static tree simplify_cond_and_lookup_avail_expr (tree, stmt_ann_t, int); static tree simplify_switch_and_lookup_avail_expr (tree, int); static tree find_equivalent_equality_comparison (tree); @@ -281,8 +280,7 @@ static void record_range (tree, basic_block); static bool extract_range_from_cond (tree, tree *, tree *, int *); static void record_equivalences_from_phis (basic_block); static void record_equivalences_from_incoming_edge (basic_block); -static bool eliminate_redundant_computations (struct dom_walk_data *, - tree, stmt_ann_t); +static bool eliminate_redundant_computations (tree, stmt_ann_t); static void record_equivalences_from_stmt (tree, int, stmt_ann_t); static void thread_across_edge (struct dom_walk_data *, edge); static void dom_opt_finalize_block (struct dom_walk_data *, basic_block); @@ -1715,8 +1713,7 @@ simple_iv_increment_p (tree stmt) the hash table and return the result. Otherwise return NULL. */ static tree -simplify_rhs_and_lookup_avail_expr (struct dom_walk_data *walk_data, - tree stmt, int insert) +simplify_rhs_and_lookup_avail_expr (tree stmt, int insert) { tree rhs = TREE_OPERAND (stmt, 1); enum tree_code rhs_code = TREE_CODE (rhs); @@ -1840,127 +1837,6 @@ simplify_rhs_and_lookup_avail_expr (struct dom_walk_data *walk_data, dont_fold_assoc:; } - /* Transform TRUNC_DIV_EXPR and TRUNC_MOD_EXPR into RSHIFT_EXPR - and BIT_AND_EXPR respectively if the first operand is greater - than zero and the second operand is an exact power of two. */ - if ((rhs_code == TRUNC_DIV_EXPR || rhs_code == TRUNC_MOD_EXPR) - && INTEGRAL_TYPE_P (TREE_TYPE (TREE_OPERAND (rhs, 0))) - && integer_pow2p (TREE_OPERAND (rhs, 1))) - { - tree val; - tree op = TREE_OPERAND (rhs, 0); - - if (TYPE_UNSIGNED (TREE_TYPE (op))) - { - val = integer_one_node; - } - else - { - tree dummy_cond = walk_data->global_data; - - if (! dummy_cond) - { - dummy_cond = build (GT_EXPR, boolean_type_node, - op, integer_zero_node); - dummy_cond = build (COND_EXPR, void_type_node, - dummy_cond, NULL, NULL); - walk_data->global_data = dummy_cond; - } - else - { - TREE_SET_CODE (COND_EXPR_COND (dummy_cond), GT_EXPR); - TREE_OPERAND (COND_EXPR_COND (dummy_cond), 0) = op; - TREE_OPERAND (COND_EXPR_COND (dummy_cond), 1) - = integer_zero_node; - } - val = simplify_cond_and_lookup_avail_expr (dummy_cond, NULL, false); - } - - if (val && integer_onep (val)) - { - tree t; - tree op0 = TREE_OPERAND (rhs, 0); - tree op1 = TREE_OPERAND (rhs, 1); - - if (rhs_code == TRUNC_DIV_EXPR) - t = build (RSHIFT_EXPR, TREE_TYPE (op0), op0, - build_int_cst (NULL_TREE, tree_log2 (op1))); - else - t = build (BIT_AND_EXPR, TREE_TYPE (op0), op0, - local_fold (build (MINUS_EXPR, TREE_TYPE (op1), - op1, integer_one_node))); - - result = update_rhs_and_lookup_avail_expr (stmt, t, insert); - } - } - - /* Transform ABS (X) into X or -X as appropriate. */ - if (rhs_code == ABS_EXPR - && INTEGRAL_TYPE_P (TREE_TYPE (TREE_OPERAND (rhs, 0)))) - { - tree val; - tree op = TREE_OPERAND (rhs, 0); - tree type = TREE_TYPE (op); - - if (TYPE_UNSIGNED (type)) - { - val = integer_zero_node; - } - else - { - tree dummy_cond = walk_data->global_data; - - if (! dummy_cond) - { - dummy_cond = build (LE_EXPR, boolean_type_node, - op, integer_zero_node); - dummy_cond = build (COND_EXPR, void_type_node, - dummy_cond, NULL, NULL); - walk_data->global_data = dummy_cond; - } - else - { - TREE_SET_CODE (COND_EXPR_COND (dummy_cond), LE_EXPR); - TREE_OPERAND (COND_EXPR_COND (dummy_cond), 0) = op; - TREE_OPERAND (COND_EXPR_COND (dummy_cond), 1) - = build_int_cst (type, 0); - } - val = simplify_cond_and_lookup_avail_expr (dummy_cond, NULL, false); - - if (!val) - { - TREE_SET_CODE (COND_EXPR_COND (dummy_cond), GE_EXPR); - TREE_OPERAND (COND_EXPR_COND (dummy_cond), 0) = op; - TREE_OPERAND (COND_EXPR_COND (dummy_cond), 1) - = build_int_cst (type, 0); - - val = simplify_cond_and_lookup_avail_expr (dummy_cond, - NULL, false); - - if (val) - { - if (integer_zerop (val)) - val = integer_one_node; - else if (integer_onep (val)) - val = integer_zero_node; - } - } - } - - if (val - && (integer_onep (val) || integer_zerop (val))) - { - tree t; - - if (integer_onep (val)) - t = build1 (NEGATE_EXPR, TREE_TYPE (op), op); - else - t = op; - - result = update_rhs_and_lookup_avail_expr (stmt, t, insert); - } - } - /* Optimize *"foo" into 'f'. This is done here rather than in fold to avoid problems with stuff like &*"foo". */ if (TREE_CODE (rhs) == INDIRECT_REF || TREE_CODE (rhs) == ARRAY_REF) @@ -2602,8 +2478,7 @@ propagate_to_outgoing_edges (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED, table. */ static bool -eliminate_redundant_computations (struct dom_walk_data *walk_data, - tree stmt, stmt_ann_t ann) +eliminate_redundant_computations (tree stmt, stmt_ann_t ann) { tree *expr_p, def = NULL_TREE; bool insert = true; @@ -2632,7 +2507,7 @@ eliminate_redundant_computations (struct dom_walk_data *walk_data, then try to simplify the RHS and lookup the new RHS in the hash table. */ if (! cached_lhs && TREE_CODE (stmt) == MODIFY_EXPR) - cached_lhs = simplify_rhs_and_lookup_avail_expr (walk_data, stmt, insert); + cached_lhs = simplify_rhs_and_lookup_avail_expr (stmt, insert); /* Similarly if this is a COND_EXPR and we did not find its expression in the hash table, simplify the condition and try again. */ @@ -2955,8 +2830,8 @@ cprop_into_stmt (tree stmt) the variable in the LHS in the CONST_AND_COPIES table. */ static void -optimize_stmt (struct dom_walk_data *walk_data, basic_block bb, - block_stmt_iterator si) +optimize_stmt (struct dom_walk_data *walk_data ATTRIBUTE_UNUSED, + basic_block bb, block_stmt_iterator si) { stmt_ann_t ann; tree stmt, old_stmt; @@ -3026,7 +2901,7 @@ optimize_stmt (struct dom_walk_data *walk_data, basic_block bb, if (may_optimize_p) may_have_exposed_new_symbols - |= eliminate_redundant_computations (walk_data, stmt, ann); + |= eliminate_redundant_computations (stmt, ann); /* Record any additional equivalences created by this statement. */ if (TREE_CODE (stmt) == MODIFY_EXPR) diff --git a/gcc/tree-vrp.c b/gcc/tree-vrp.c index 35f78f4b8552..89dae4b850de 100644 --- a/gcc/tree-vrp.c +++ b/gcc/tree-vrp.c @@ -94,6 +94,21 @@ static sbitmap blocks_visited; of values that SSA name N_I may take. */ static value_range_t **vr_value; +/* Local version of fold that doesn't introduce cruft. */ + +static tree +local_fold (tree t) +{ + t = fold (t); + + /* Strip away useless type conversions. Both the NON_LVALUE_EXPR that + may have been added by fold, and "useless" type conversions that might + now be apparent due to propagation. */ + STRIP_USELESS_TYPE_CONVERSION (t); + + return t; +} + /* Given a comparison code, return its opposite. Note that this is *not* the same as inverting its truth value (invert_tree_comparison). Here we just want to literally flip the comparison around. @@ -3402,6 +3417,124 @@ varying: return SSA_PROP_VARYING; } +/* Walk through the IL simplifying expressions using knowledge + gathered by VRP. */ + +static void +simplify_using_ranges (void) +{ + basic_block bb; + + FOR_EACH_BB (bb) + { + block_stmt_iterator bsi; + + for (bsi = bsi_start (bb); !bsi_end_p (bsi); bsi_next (&bsi)) + { + tree stmt = bsi_stmt (bsi); + + if (TREE_CODE (stmt) == MODIFY_EXPR) + { + tree rhs = TREE_OPERAND (stmt, 1); + enum tree_code rhs_code = TREE_CODE (rhs); + + /* Transform TRUNC_DIV_EXPR and TRUNC_MOD_EXPR into RSHIFT_EXPR + and BIT_AND_EXPR respectively if the first operand is greater + than zero and the second operand is an exact power of two. */ + if ((rhs_code == TRUNC_DIV_EXPR || rhs_code == TRUNC_MOD_EXPR) + && INTEGRAL_TYPE_P (TREE_TYPE (TREE_OPERAND (rhs, 0))) + && integer_pow2p (TREE_OPERAND (rhs, 1))) + { + tree val = NULL; + tree op = TREE_OPERAND (rhs, 0); + value_range_t *vr = get_value_range (TREE_OPERAND (rhs, 0)); + + if (TYPE_UNSIGNED (TREE_TYPE (op))) + { + val = integer_one_node; + } + else + { + val = compare_range_with_value (GT_EXPR, vr, + integer_zero_node); + } + + if (val && integer_onep (val)) + { + tree t; + tree op0 = TREE_OPERAND (rhs, 0); + tree op1 = TREE_OPERAND (rhs, 1); + + if (rhs_code == TRUNC_DIV_EXPR) + t = build (RSHIFT_EXPR, TREE_TYPE (op0), op0, + build_int_cst (NULL_TREE, tree_log2 (op1))); + else + t = build (BIT_AND_EXPR, TREE_TYPE (op0), op0, + local_fold (build (MINUS_EXPR, + TREE_TYPE (op1), + op1, + integer_one_node))); + + TREE_OPERAND (stmt, 1) = t; + update_stmt (stmt); + } + + } + + /* Transform ABS (X) into X or -X as appropriate. */ + if (rhs_code == ABS_EXPR + && TREE_CODE (TREE_OPERAND (rhs, 0)) == SSA_NAME + && INTEGRAL_TYPE_P (TREE_TYPE (TREE_OPERAND (rhs, 0)))) + { + tree val = NULL; + tree op = TREE_OPERAND (rhs, 0); + tree type = TREE_TYPE (op); + value_range_t *vr = get_value_range (TREE_OPERAND (rhs, 0)); + + if (TYPE_UNSIGNED (type)) + { + val = integer_zero_node; + } + else if (vr) + { + val = compare_range_with_value (LE_EXPR, vr, + integer_zero_node); + if (!val) + { + val = compare_range_with_value (GE_EXPR, vr, + integer_zero_node); + + if (val) + { + if (integer_zerop (val)) + val = integer_one_node; + else if (integer_onep (val)) + val = integer_zero_node; + } + } + + if (val + && (integer_onep (val) || integer_zerop (val))) + { + tree t; + + if (integer_onep (val)) + t = build1 (NEGATE_EXPR, TREE_TYPE (op), op); + else + t = op; + + TREE_OPERAND (stmt, 1) = t; + update_stmt (stmt); + } + } + } + } + + /* TODO. Simplify conditionals. */ + } + } +} + /* Traverse all the blocks folding conditionals with known ranges. */ @@ -3445,6 +3578,12 @@ vrp_finalize (void) substitute_and_fold (single_val_range, true); + /* One could argue all simplifications should be done here + rather than using substitute_and_fold since this code + is going to have to perform a complete walk through the + IL anyway. */ + simplify_using_ranges (); + /* Free allocated memory. */ for (i = 0; i < num_ssa_names; i++) if (vr_value[i]) -- GitLab