This is the mail archive of the gcc-patches@gcc.gnu.org mailing list for the GCC project.


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]
Other format: [Raw text]

Re: [PATCH] Introduce __builtin_expect_with_probability (PR target/83610).


> Hi.
> 
> This is implementation of new built-in that can be used for more fine
> tweaking of probability. Micro benchmark is attached as part of the PR.
> 
> Patch can bootstrap on ppc64le-redhat-linux and survives regression tests.
> 
> Ready to be installed?

It reasonale to me to add the fature. Years ago I made similar patch and at
that time it did not go in based on argumentation that programers are not good
on guessing probabilities and this is too much of fine control while it should
be done by profile feedback. 

However I guess it is better to have way to specify probability than tweak with
--param that controls the builtin_expect outcome globally.

What I think would be useful is to tie this to the code giving loop trip
estimate.  If you know that the loop iterates 100 times at the average, you
can specify probability 1%.   For this it seems to me more sensible to have
the percentage parameter to be double rather than long so one can specify larger
trip counts this way.

Honza


> Martin
> 
> gcc/ChangeLog:
> 
> 2018-07-24  Martin Liska  <mliska@suse.cz>
> 
>         PR target/83610
> 	* builtin-types.def (BT_FN_LONG_LONG_LONG_LONG): New type.
> 	* builtins.c (expand_builtin_expect_with_probability):
>         New function.
> 	(expand_builtin): Handle also BUILT_IN_EXPECT_WITH_PROBABILITY.
> 	(build_builtin_expect_predicate): Likewise.
> 	(fold_builtin_expect): Likewise.
> 	(fold_builtin_2): Likewise.
> 	(fold_builtin_3): Likewise.
> 	* builtins.def (BUILT_IN_EXPECT_WITH_PROBABILITY): Define new
>         builtin.
> 	* builtins.h (fold_builtin_expect): Add new argument
>         (probability).
> 	* doc/extend.texi: Document the new builtin.
> 	* doc/invoke.texi: Likewise.
> 	* gimple-fold.c (gimple_fold_call): Pass new argument.
> 	* ipa-fnsummary.c (find_foldable_builtin_expect):
>         Handle also BUILT_IN_EXPECT_WITH_PROBABILITY.
> 	* predict.c (expr_expected_value): Add new out argument which
>         is probability.
> 	(expr_expected_value_1): Likewise.
> 	(tree_predict_by_opcode): Predict edge based on
>         provided probability.
> 	(pass_strip_predict_hints::execute): Use newly added
>         DECL_BUILT_IN_P macro.
> 	* predict.def (PRED_BUILTIN_EXPECT_WITH_PROBABILITY):
>         Define new predictor.
> 	* tree.h (DECL_BUILT_IN_P): Define.
> 
> gcc/testsuite/ChangeLog:
> 
> 2018-07-24  Martin Liska  <mliska@suse.cz>
> 
> 	* gcc.dg/predict-16.c: New test.
> ---
>  gcc/builtin-types.def             |  2 +
>  gcc/builtins.c                    | 65 ++++++++++++++++++++++++-------
>  gcc/builtins.def                  |  1 +
>  gcc/builtins.h                    |  2 +-
>  gcc/doc/extend.texi               |  8 ++++
>  gcc/doc/invoke.texi               |  3 ++
>  gcc/gimple-fold.c                 |  3 +-
>  gcc/ipa-fnsummary.c               |  1 +
>  gcc/predict.c                     | 61 ++++++++++++++++++++++-------
>  gcc/predict.def                   |  5 +++
>  gcc/testsuite/gcc.dg/predict-16.c | 13 +++++++
>  gcc/tree.h                        |  6 +++
>  12 files changed, 140 insertions(+), 30 deletions(-)
>  create mode 100644 gcc/testsuite/gcc.dg/predict-16.c
> 
> 

> diff --git a/gcc/builtin-types.def b/gcc/builtin-types.def
> index b01095c420f..6e87bcbbf1d 100644
> --- a/gcc/builtin-types.def
> +++ b/gcc/builtin-types.def
> @@ -531,6 +531,8 @@ DEF_FUNCTION_TYPE_3 (BT_FN_ULONG_ULONG_ULONG_ULONG,
>  		     BT_ULONG, BT_ULONG, BT_ULONG, BT_ULONG)
>  DEF_FUNCTION_TYPE_3 (BT_FN_LONG_LONG_UINT_UINT,
>  		     BT_LONG, BT_LONG, BT_UINT, BT_UINT)
> +DEF_FUNCTION_TYPE_3 (BT_FN_LONG_LONG_LONG_LONG,
> +		     BT_LONG, BT_LONG, BT_LONG, BT_LONG)
>  DEF_FUNCTION_TYPE_3 (BT_FN_ULONG_ULONG_UINT_UINT,
>  		     BT_ULONG, BT_ULONG, BT_UINT, BT_UINT)
>  DEF_FUNCTION_TYPE_3 (BT_FN_STRING_CONST_STRING_CONST_STRING_INT,
> diff --git a/gcc/builtins.c b/gcc/builtins.c
> index 539a6d17688..29d77d3d83b 100644
> --- a/gcc/builtins.c
> +++ b/gcc/builtins.c
> @@ -148,6 +148,7 @@ static rtx expand_builtin_unop (machine_mode, tree, rtx, rtx, optab);
>  static rtx expand_builtin_frame_address (tree, tree);
>  static tree stabilize_va_list_loc (location_t, tree, int);
>  static rtx expand_builtin_expect (tree, rtx);
> +static rtx expand_builtin_expect_with_probability (tree, rtx);
>  static tree fold_builtin_constant_p (tree);
>  static tree fold_builtin_classify_type (tree);
>  static tree fold_builtin_strlen (location_t, tree, tree);
> @@ -5237,6 +5238,27 @@ expand_builtin_expect (tree exp, rtx target)
>    return target;
>  }
>  
> +/* Expand a call to __builtin_expect_with_probability.  We just return our
> +   argument as the builtin_expect semantic should've been already executed by
> +   tree branch prediction pass.  */
> +
> +static rtx
> +expand_builtin_expect_with_probability (tree exp, rtx target)
> +{
> +  tree arg;
> +
> +  if (call_expr_nargs (exp) < 3)
> +    return const0_rtx;
> +  arg = CALL_EXPR_ARG (exp, 0);
> +
> +  target = expand_expr (arg, target, VOIDmode, EXPAND_NORMAL);
> +  /* When guessing was done, the hints should be already stripped away.  */
> +  gcc_assert (!flag_guess_branch_prob
> +	      || optimize == 0 || seen_error ());
> +  return target;
> +}
> +
> +
>  /* Expand a call to __builtin_assume_aligned.  We just return our first
>     argument as the builtin_assume_aligned semantic should've been already
>     executed by CCP.  */
> @@ -7494,6 +7516,8 @@ expand_builtin (tree exp, rtx target, rtx subtarget, machine_mode mode,
>        return expand_builtin_va_copy (exp);
>      case BUILT_IN_EXPECT:
>        return expand_builtin_expect (exp, target);
> +    case BUILT_IN_EXPECT_WITH_PROBABILITY:
> +      return expand_builtin_expect_with_probability (exp, target);
>      case BUILT_IN_ASSUME_ALIGNED:
>        return expand_builtin_assume_aligned (exp, target);
>      case BUILT_IN_PREFETCH:
> @@ -8134,16 +8158,20 @@ fold_builtin_constant_p (tree arg)
>    return NULL_TREE;
>  }
>  
> -/* Create builtin_expect with PRED and EXPECTED as its arguments and
> -   return it as a truthvalue.  */
> +/* Create builtin_expect or builtin_expect_with_probability
> +   with PRED and EXPECTED as its arguments and return it as a truthvalue.
> +   Fortran FE can also produce builtin_expect with PREDICTOR as third argument.
> +   builtin_expect_with_probability instead uses third argument as PROBABILITY
> +   value.  */
>  
>  static tree
>  build_builtin_expect_predicate (location_t loc, tree pred, tree expected,
> -				tree predictor)
> +				tree predictor, tree probability)
>  {
>    tree fn, arg_types, pred_type, expected_type, call_expr, ret_type;
>  
> -  fn = builtin_decl_explicit (BUILT_IN_EXPECT);
> +  fn = builtin_decl_explicit (probability == NULL_TREE ? BUILT_IN_EXPECT
> +			      : BUILT_IN_EXPECT_WITH_PROBABILITY);
>    arg_types = TYPE_ARG_TYPES (TREE_TYPE (fn));
>    ret_type = TREE_TYPE (TREE_TYPE (fn));
>    pred_type = TREE_VALUE (arg_types);
> @@ -8151,18 +8179,23 @@ build_builtin_expect_predicate (location_t loc, tree pred, tree expected,
>  
>    pred = fold_convert_loc (loc, pred_type, pred);
>    expected = fold_convert_loc (loc, expected_type, expected);
> -  call_expr = build_call_expr_loc (loc, fn, predictor ? 3 : 2, pred, expected,
> -				   predictor);
> +
> +  if (probability)
> +    call_expr = build_call_expr_loc (loc, fn, 3, pred, expected, probability);
> +  else
> +    call_expr = build_call_expr_loc (loc, fn, predictor ? 3 : 2, pred, expected,
> +				     predictor);
>  
>    return build2 (NE_EXPR, TREE_TYPE (pred), call_expr,
>  		 build_int_cst (ret_type, 0));
>  }
>  
> -/* Fold a call to builtin_expect with arguments ARG0 and ARG1.  Return
> +/* Fold a call to builtin_expect with arguments ARG0, ARG1, ARG2, ARG3.  Return
>     NULL_TREE if no simplification is possible.  */
>  
>  tree
> -fold_builtin_expect (location_t loc, tree arg0, tree arg1, tree arg2)
> +fold_builtin_expect (location_t loc, tree arg0, tree arg1, tree arg2,
> +		     tree arg3)
>  {
>    tree inner, fndecl, inner_arg0;
>    enum tree_code code;
> @@ -8186,8 +8219,9 @@ fold_builtin_expect (location_t loc, tree arg0, tree arg1, tree arg2)
>  
>    if (TREE_CODE (inner) == CALL_EXPR
>        && (fndecl = get_callee_fndecl (inner))
> -      && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL
> -      && DECL_FUNCTION_CODE (fndecl) == BUILT_IN_EXPECT)
> +      && (DECL_BUILT_IN_P (fndecl, BUILT_IN_NORMAL, BUILT_IN_EXPECT)
> +	  || DECL_BUILT_IN_P (fndecl, BUILT_IN_NORMAL,
> +			      BUILT_IN_EXPECT_WITH_PROBABILITY)))
>      return arg0;
>  
>    inner = inner_arg0;
> @@ -8198,8 +8232,8 @@ fold_builtin_expect (location_t loc, tree arg0, tree arg1, tree arg2)
>        tree op1 = TREE_OPERAND (inner, 1);
>        arg1 = save_expr (arg1);
>  
> -      op0 = build_builtin_expect_predicate (loc, op0, arg1, arg2);
> -      op1 = build_builtin_expect_predicate (loc, op1, arg1, arg2);
> +      op0 = build_builtin_expect_predicate (loc, op0, arg1, arg2, arg3);
> +      op1 = build_builtin_expect_predicate (loc, op1, arg1, arg2, arg3);
>        inner = build2 (code, TREE_TYPE (inner), op0, op1);
>  
>        return fold_convert_loc (loc, TREE_TYPE (arg0), inner);
> @@ -9295,7 +9329,7 @@ fold_builtin_2 (location_t loc, tree fndecl, tree arg0, tree arg1)
>        return fold_builtin_strpbrk (loc, arg0, arg1, type);
>  
>      case BUILT_IN_EXPECT:
> -      return fold_builtin_expect (loc, arg0, arg1, NULL_TREE);
> +      return fold_builtin_expect (loc, arg0, arg1, NULL_TREE, NULL_TREE);
>  
>      case BUILT_IN_ISGREATER:
>        return fold_builtin_unordered_cmp (loc, fndecl,
> @@ -9373,7 +9407,10 @@ fold_builtin_3 (location_t loc, tree fndecl,
>        return fold_builtin_memcmp (loc, arg0, arg1, arg2);
>  
>      case BUILT_IN_EXPECT:
> -      return fold_builtin_expect (loc, arg0, arg1, arg2);
> +      return fold_builtin_expect (loc, arg0, arg1, arg2, NULL_TREE);
> +
> +    case BUILT_IN_EXPECT_WITH_PROBABILITY:
> +      return fold_builtin_expect (loc, arg0, arg1, NULL_TREE, arg2);
>  
>      case BUILT_IN_ADD_OVERFLOW:
>      case BUILT_IN_SUB_OVERFLOW:
> diff --git a/gcc/builtins.def b/gcc/builtins.def
> index aacbd513a16..683a07e18fa 100644
> --- a/gcc/builtins.def
> +++ b/gcc/builtins.def
> @@ -848,6 +848,7 @@ DEF_EXT_LIB_BUILTIN        (BUILT_IN_EXECVP, "execvp", BT_FN_INT_CONST_STRING_PT
>  DEF_EXT_LIB_BUILTIN        (BUILT_IN_EXECVE, "execve", BT_FN_INT_CONST_STRING_PTR_CONST_STRING_PTR_CONST_STRING, ATTR_NOTHROW_LIST)
>  DEF_LIB_BUILTIN        (BUILT_IN_EXIT, "exit", BT_FN_VOID_INT, ATTR_NORETURN_NOTHROW_LIST)
>  DEF_GCC_BUILTIN        (BUILT_IN_EXPECT, "expect", BT_FN_LONG_LONG_LONG, ATTR_CONST_NOTHROW_LEAF_LIST)
> +DEF_GCC_BUILTIN        (BUILT_IN_EXPECT_WITH_PROBABILITY, "expect_with_probability", BT_FN_LONG_LONG_LONG_LONG, ATTR_CONST_NOTHROW_LEAF_LIST)
>  DEF_GCC_BUILTIN        (BUILT_IN_ASSUME_ALIGNED, "assume_aligned", BT_FN_PTR_CONST_PTR_SIZE_VAR, ATTR_CONST_NOTHROW_LEAF_LIST)
>  DEF_GCC_BUILTIN        (BUILT_IN_EXTEND_POINTER, "extend_pointer", BT_FN_UNWINDWORD_PTR, ATTR_CONST_NOTHROW_LEAF_LIST)
>  DEF_GCC_BUILTIN        (BUILT_IN_EXTRACT_RETURN_ADDR, "extract_return_addr", BT_FN_PTR_PTR, ATTR_LEAF_LIST)
> diff --git a/gcc/builtins.h b/gcc/builtins.h
> index c9229049e21..3662ebcd98f 100644
> --- a/gcc/builtins.h
> +++ b/gcc/builtins.h
> @@ -76,7 +76,7 @@ extern void expand_ifn_atomic_compare_exchange (gcall *);
>  extern rtx expand_builtin (tree, rtx, rtx, machine_mode, int);
>  extern rtx expand_builtin_with_bounds (tree, rtx, rtx, machine_mode, int);
>  extern enum built_in_function builtin_mathfn_code (const_tree);
> -extern tree fold_builtin_expect (location_t, tree, tree, tree);
> +extern tree fold_builtin_expect (location_t, tree, tree, tree, tree);
>  extern bool avoid_folding_inline_builtin (tree);
>  extern tree fold_call_expr (location_t, tree, bool);
>  extern tree fold_builtin_call_array (location_t, tree, tree, int, tree *);
> diff --git a/gcc/doc/extend.texi b/gcc/doc/extend.texi
> index 7b471ec40f7..8567b24f873 100644
> --- a/gcc/doc/extend.texi
> +++ b/gcc/doc/extend.texi
> @@ -11852,6 +11852,14 @@ if (__builtin_expect (ptr != NULL, 1))
>  when testing pointer or floating-point values.
>  @end deftypefn
>  
> +@deftypefn {Built-in Function} long __builtin_expect_with_probability
> +(long @var{exp}, long @var{c}, long @var{probability})
> +
> +The built-in has same semantics as @code{__builtin_expect_with_probability},
> +but user can provide expected probability (in percent) for value of @var{exp}.
> +Valid values of @var{probability} argument are in inclusive range 0 and 100.
> +@end deftypefn
> +
>  @deftypefn {Built-in Function} void __builtin_trap (void)
>  This function causes the program to exit abnormally.  GCC implements
>  this function by using a target-dependent mechanism (such as
> diff --git a/gcc/doc/invoke.texi b/gcc/doc/invoke.texi
> index 1dcdfb51c47..edc46a3be95 100644
> --- a/gcc/doc/invoke.texi
> +++ b/gcc/doc/invoke.texi
> @@ -9209,6 +9209,9 @@ between the heuristics and @code{__builtin_expect} can be complex, and in
>  some cases, it may be useful to disable the heuristics so that the effects
>  of @code{__builtin_expect} are easier to understand.
>  
> +It is also possible to specify expected probability of the expression
> +with @code{__builtin_expect_with_probability} built-in function.
> +
>  The default is @option{-fguess-branch-probability} at levels
>  @option{-O}, @option{-O2}, @option{-O3}, @option{-Os}.
>  
> diff --git a/gcc/gimple-fold.c b/gcc/gimple-fold.c
> index 027ca4da97c..ea441797214 100644
> --- a/gcc/gimple-fold.c
> +++ b/gcc/gimple-fold.c
> @@ -4166,7 +4166,8 @@ gimple_fold_call (gimple_stmt_iterator *gsi, bool inplace)
>  	  result = fold_builtin_expect (gimple_location (stmt),
>  					gimple_call_arg (stmt, 0),
>  					gimple_call_arg (stmt, 1),
> -					gimple_call_arg (stmt, 2));
> +					gimple_call_arg (stmt, 2),
> +					NULL_TREE);
>  	  break;
>  	case IFN_UBSAN_OBJECT_SIZE:
>  	  {
> diff --git a/gcc/ipa-fnsummary.c b/gcc/ipa-fnsummary.c
> index c99718a265f..a8fc2c2df9a 100644
> --- a/gcc/ipa-fnsummary.c
> +++ b/gcc/ipa-fnsummary.c
> @@ -1851,6 +1851,7 @@ find_foldable_builtin_expect (basic_block bb)
>      {
>        gimple *stmt = gsi_stmt (bsi);
>        if (gimple_call_builtin_p (stmt, BUILT_IN_EXPECT)
> +	  || gimple_call_builtin_p (stmt, BUILT_IN_EXPECT_WITH_PROBABILITY)
>  	  || gimple_call_internal_p (stmt, IFN_BUILTIN_EXPECT))
>          {
>            tree var = gimple_call_lhs (stmt);
> diff --git a/gcc/predict.c b/gcc/predict.c
> index 65e088fb8df..73e2a0fd2ed 100644
> --- a/gcc/predict.c
> +++ b/gcc/predict.c
> @@ -2262,13 +2262,15 @@ guess_outgoing_edge_probabilities (basic_block bb)
>    combine_predictions_for_insn (BB_END (bb), bb);
>  }
>  
> -static tree expr_expected_value (tree, bitmap, enum br_predictor *predictor);
> +static tree expr_expected_value (tree, bitmap, enum br_predictor *predictor,
> +				 tree *probability);
>  
>  /* Helper function for expr_expected_value.  */
>  
>  static tree
>  expr_expected_value_1 (tree type, tree op0, enum tree_code code,
> -		       tree op1, bitmap visited, enum br_predictor *predictor)
> +		       tree op1, bitmap visited, enum br_predictor *predictor,
> +		       tree *probability)
>  {
>    gimple *def;
>  
> @@ -2329,7 +2331,8 @@ expr_expected_value_1 (tree type, tree op0, enum tree_code code,
>  	      if (arg == PHI_RESULT (def))
>  		continue;
>  
> -	      new_val = expr_expected_value (arg, visited, &predictor2);
> +	      new_val = expr_expected_value (arg, visited, &predictor2,
> +					     probability);
>  
>  	      /* It is difficult to combine value predictors.  Simply assume
>  		 that later predictor is weaker and take its prediction.  */
> @@ -2353,7 +2356,7 @@ expr_expected_value_1 (tree type, tree op0, enum tree_code code,
>  					gimple_assign_rhs1 (def),
>  					gimple_assign_rhs_code (def),
>  					gimple_assign_rhs2 (def),
> -					visited, predictor);
> +					visited, predictor, NULL);
>  	}
>  
>        if (is_gimple_call (def))
> @@ -2395,6 +2398,21 @@ expr_expected_value_1 (tree type, tree op0, enum tree_code code,
>  		    *predictor = PRED_BUILTIN_EXPECT;
>  		  return gimple_call_arg (def, 1);
>  		}
> +	      case BUILT_IN_EXPECT_WITH_PROBABILITY:
> +		{
> +		  tree val;
> +		  if (gimple_call_num_args (def) != 3)
> +		    return NULL;
> +		  val = gimple_call_arg (def, 0);
> +		  if (TREE_CONSTANT (val))
> +		    return val;
> +		  if (predictor)
> +		    {
> +		      *predictor = PRED_BUILTIN_EXPECT_WITH_PROBABILITY;
> +		      *probability = gimple_call_arg (def, 2);
> +		    }
> +		  return gimple_call_arg (def, 1);
> +		}
>  
>  	      case BUILT_IN_SYNC_BOOL_COMPARE_AND_SWAP_N:
>  	      case BUILT_IN_SYNC_BOOL_COMPARE_AND_SWAP_1:
> @@ -2426,10 +2444,10 @@ expr_expected_value_1 (tree type, tree op0, enum tree_code code,
>      {
>        tree res;
>        enum br_predictor predictor2;
> -      op0 = expr_expected_value (op0, visited, predictor);
> +      op0 = expr_expected_value (op0, visited, predictor, probability);
>        if (!op0)
>  	return NULL;
> -      op1 = expr_expected_value (op1, visited, &predictor2);
> +      op1 = expr_expected_value (op1, visited, &predictor2, probability);
>        if (predictor && *predictor < predictor2)
>  	*predictor = predictor2;
>        if (!op1)
> @@ -2442,7 +2460,7 @@ expr_expected_value_1 (tree type, tree op0, enum tree_code code,
>    if (get_gimple_rhs_class (code) == GIMPLE_UNARY_RHS)
>      {
>        tree res;
> -      op0 = expr_expected_value (op0, visited, predictor);
> +      op0 = expr_expected_value (op0, visited, predictor, probability);
>        if (!op0)
>  	return NULL;
>        res = fold_build1 (code, type, op0);
> @@ -2463,7 +2481,7 @@ expr_expected_value_1 (tree type, tree op0, enum tree_code code,
>  
>  static tree
>  expr_expected_value (tree expr, bitmap visited,
> -		     enum br_predictor *predictor)
> +		     enum br_predictor *predictor, tree *probability)
>  {
>    enum tree_code code;
>    tree op0, op1;
> @@ -2477,7 +2495,8 @@ expr_expected_value (tree expr, bitmap visited,
>  
>    extract_ops_from_tree (expr, &code, &op0, &op1);
>    return expr_expected_value_1 (TREE_TYPE (expr),
> -				op0, code, op1, visited, predictor);
> +				op0, code, op1, visited, predictor,
> +				probability);
>  }
>  
>  /* Predict using opcode of the last statement in basic block.  */
> @@ -2488,7 +2507,7 @@ tree_predict_by_opcode (basic_block bb)
>    edge then_edge;
>    tree op0, op1;
>    tree type;
> -  tree val;
> +  tree val, probability;
>    enum tree_code cmp;
>    edge_iterator ei;
>    enum br_predictor predictor;
> @@ -2503,7 +2522,7 @@ tree_predict_by_opcode (basic_block bb)
>    cmp = gimple_cond_code (stmt);
>    type = TREE_TYPE (op0);
>    val = expr_expected_value_1 (boolean_type_node, op0, cmp, op1, auto_bitmap (),
> -			       &predictor);
> +			       &predictor, &probability);
>    if (val && TREE_CODE (val) == INTEGER_CST)
>      {
>        if (predictor == PRED_BUILTIN_EXPECT)
> @@ -2515,6 +2534,19 @@ tree_predict_by_opcode (basic_block bb)
>  	    percent = 100 - percent;
>  	  predict_edge (then_edge, PRED_BUILTIN_EXPECT, HITRATE (percent));
>  	}
> +      else if (predictor == PRED_BUILTIN_EXPECT_WITH_PROBABILITY)
> +	{
> +	  if (!tree_fits_uhwi_p (probability))
> +	    return;
> +
> +	  unsigned percent = tree_to_uhwi (probability);
> +	  if (integer_zerop (val))
> +	    percent = 100 - percent;
> +	  if (percent > 100)
> +	    return;
> +	  predict_edge (then_edge, PRED_BUILTIN_EXPECT_WITH_PROBABILITY,
> +			HITRATE (percent));
> +	}
>        else
>  	predict_edge_def (then_edge, predictor,
>  			  integer_zerop (val) ? NOT_TAKEN : TAKEN);
> @@ -3927,10 +3959,11 @@ pass_strip_predict_hints::execute (function *fun)
>  	    {
>  	      tree fndecl = gimple_call_fndecl (stmt);
>  
> -	      if ((fndecl
> -		   && DECL_BUILT_IN_CLASS (fndecl) == BUILT_IN_NORMAL
> -		   && DECL_FUNCTION_CODE (fndecl) == BUILT_IN_EXPECT
> +	      if ((DECL_BUILT_IN_P (fndecl, BUILT_IN_NORMAL, BUILT_IN_EXPECT)
>  		   && gimple_call_num_args (stmt) == 2)
> +		  || (DECL_BUILT_IN_P (fndecl, BUILT_IN_NORMAL,
> +				       BUILT_IN_EXPECT_WITH_PROBABILITY)
> +		      && gimple_call_num_args (stmt) == 3)
>  		  || (gimple_call_internal_p (stmt)
>  		      && gimple_call_internal_fn (stmt) == IFN_BUILTIN_EXPECT))
>  		{
> diff --git a/gcc/predict.def b/gcc/predict.def
> index 4ed97ed165c..b929d4c37db 100644
> --- a/gcc/predict.def
> +++ b/gcc/predict.def
> @@ -69,6 +69,11 @@ DEF_PREDICTOR (PRED_COMPARE_AND_SWAP, "compare and swap", PROB_VERY_LIKELY,
>  DEF_PREDICTOR (PRED_BUILTIN_EXPECT, "__builtin_expect", PROB_VERY_LIKELY,
>  	       PRED_FLAG_FIRST_MATCH)
>  
> +/* Hints provided by user via __builtin_expect_with_probability.  */
> +DEF_PREDICTOR (PRED_BUILTIN_EXPECT_WITH_PROBABILITY,
> +	       "__builtin_expect_with_probability", PROB_UNINITIALIZED,
> +	       PRED_FLAG_FIRST_MATCH)
> +
>  /* Use number of loop iterations guessed by the contents of the loop.  */
>  DEF_PREDICTOR (PRED_LOOP_ITERATIONS_GUESSED, "guessed loop iterations",
>  	       PROB_UNINITIALIZED, PRED_FLAG_FIRST_MATCH)
> diff --git a/gcc/testsuite/gcc.dg/predict-16.c b/gcc/testsuite/gcc.dg/predict-16.c
> new file mode 100644
> index 00000000000..043f154f19f
> --- /dev/null
> +++ b/gcc/testsuite/gcc.dg/predict-16.c
> @@ -0,0 +1,13 @@
> +/* { dg-do compile } */
> +/* { dg-options "-O2 -fdump-tree-profile_estimate" } */
> +
> +extern int global;
> +
> +void foo (int base)
> +{
> +  if (__builtin_expect_with_probability (base == 100, 1, 99))
> +    global++;
> +}
> +
> +/* { dg-final { scan-tree-dump "first match heuristics: 99.0%" "profile_estimate"} } */
> +/* { dg-final { scan-tree-dump "__builtin_expect_with_probability heuristics of edge .*->.*: 99.0%" "profile_estimate"} } */
> diff --git a/gcc/tree.h b/gcc/tree.h
> index 70ac78130c0..ae00e6e4035 100644
> --- a/gcc/tree.h
> +++ b/gcc/tree.h
> @@ -3008,6 +3008,12 @@ extern vec<tree, va_gc> **decl_debug_args_insert (tree);
>  #define DECL_BUILT_IN_CLASS(NODE) \
>     (FUNCTION_DECL_CHECK (NODE)->function_decl.built_in_class)
>  
> +/* For a function declaration, return true if NODE is non-null and it is
> +   a builtin of a CLASS with requested NAME.  */
> +#define DECL_BUILT_IN_P(NODE, CLASS, NAME) \
> +  (NODE != NULL_TREE && DECL_BUILT_IN_CLASS (NODE) == CLASS \
> +   && DECL_FUNCTION_CODE (NODE) == NAME)
> +
>  /* In FUNCTION_DECL, a chain of ..._DECL nodes.  */
>  #define DECL_ARGUMENTS(NODE) \
>     (FUNCTION_DECL_CHECK (NODE)->function_decl.arguments)
> 


Index Nav: [Date Index] [Subject Index] [Author Index] [Thread Index]
Message Nav: [Date Prev] [Date Next] [Thread Prev] [Thread Next]