From 722356ce27601ee33c0aabfa939af8367ac11d54 Mon Sep 17 00:00:00 2001
From: Eric Botcazou <ebotcazou@adacore.com>
Date: Wed, 12 Oct 2011 22:09:21 +0000
Subject: [PATCH] trans.c (Attribute_to_gnu): Use remove_conversions.

	* gcc-interface/trans.c (Attribute_to_gnu): Use remove_conversions.
	(push_range_check_info): Likewise.
	(gnat_to_gnu) <N_Code_Statement>: Likewise.
	* gcc-interface/utils2.c (build_unary_op) <INDIRECT_REF>: Likewise.
	(gnat_invariant_expr): Likewise.
	* gcc-interface/utils.c (compute_related_constant): Likewise.
	(max_size): Fix handling of SAVE_EXPR.
	(remove_conversions): Fix formatting.

From-SVN: r179873
---
 gcc/ada/ChangeLog              | 11 +++++++++++
 gcc/ada/gcc-interface/trans.c  | 17 +++++------------
 gcc/ada/gcc-interface/utils.c  | 17 +++++++++--------
 gcc/ada/gcc-interface/utils2.c | 16 ++++------------
 4 files changed, 29 insertions(+), 32 deletions(-)

diff --git a/gcc/ada/ChangeLog b/gcc/ada/ChangeLog
index 07a734e77296..a6cc689e91cb 100644
--- a/gcc/ada/ChangeLog
+++ b/gcc/ada/ChangeLog
@@ -1,3 +1,14 @@
+2011-10-12  Eric Botcazou  <ebotcazou@adacore.com>
+
+	* gcc-interface/trans.c (Attribute_to_gnu): Use remove_conversions.
+	(push_range_check_info): Likewise.
+	(gnat_to_gnu) <N_Code_Statement>: Likewise.
+	* gcc-interface/utils2.c (build_unary_op) <INDIRECT_REF>: Likewise.
+	(gnat_invariant_expr): Likewise.
+	* gcc-interface/utils.c (compute_related_constant): Likewise.
+	(max_size): Fix handling of SAVE_EXPR.
+	(remove_conversions): Fix formatting.
+
 2011-10-12  Eric Botcazou  <ebotcazou@adacore.com>
 
 	* gcc-interface/ada-tree.h (DECL_LOOP_PARM_P): New flag.
diff --git a/gcc/ada/gcc-interface/trans.c b/gcc/ada/gcc-interface/trans.c
index cd84dc7eaf25..faf5eb3f3ea3 100644
--- a/gcc/ada/gcc-interface/trans.c
+++ b/gcc/ada/gcc-interface/trans.c
@@ -1364,10 +1364,7 @@ Attribute_to_gnu (Node_Id gnat_node, tree *gnu_result_type_p, int attribute)
 	 don't try to build a trampoline.  */
       if (attribute == Attr_Code_Address)
 	{
-	  for (gnu_expr = gnu_result;
-	       CONVERT_EXPR_P (gnu_expr);
-	       gnu_expr = TREE_OPERAND (gnu_expr, 0))
-	    TREE_CONSTANT (gnu_expr) = 1;
+	  gnu_expr = remove_conversions (gnu_result, false);
 
 	  if (TREE_CODE (gnu_expr) == ADDR_EXPR)
 	    TREE_NO_TRAMPOLINE (gnu_expr) = TREE_CONSTANT (gnu_expr) = 1;
@@ -1378,10 +1375,7 @@ Attribute_to_gnu (Node_Id gnat_node, tree *gnu_result_type_p, int attribute)
 	 a useful warning with -Wtrampolines.  */
       else if (TREE_CODE (TREE_TYPE (gnu_prefix)) == FUNCTION_TYPE)
 	{
-	  for (gnu_expr = gnu_result;
-	       CONVERT_EXPR_P (gnu_expr);
-	       gnu_expr = TREE_OPERAND (gnu_expr, 0))
-	    ;
+	  gnu_expr = remove_conversions (gnu_result, false);
 
 	  if (TREE_CODE (gnu_expr) == ADDR_EXPR
 	      && decl_function_context (TREE_OPERAND (gnu_expr, 0)))
@@ -2156,8 +2150,7 @@ push_range_check_info (tree var)
   if (VEC_empty (loop_info, gnu_loop_stack))
     return NULL;
 
-  while (CONVERT_EXPR_P (var) || TREE_CODE (var) == VIEW_CONVERT_EXPR)
-    var = TREE_OPERAND (var, 0);
+  var = remove_conversions (var, false);
 
   if (TREE_CODE (var) != VAR_DECL)
     return NULL;
@@ -6139,7 +6132,7 @@ gnat_to_gnu (Node_Id gnat_node)
 		     is modelled on the C front-end.  */
 		  if (!allows_reg)
 		    {
-		      STRIP_NOPS (output);
+		      output = remove_conversions (output, false);
 		      if (TREE_CODE (output) == CONST_DECL
 			  && DECL_CONST_CORRESPONDING_VAR (output))
 			output = DECL_CONST_CORRESPONDING_VAR (output);
@@ -6167,7 +6160,7 @@ gnat_to_gnu (Node_Id gnat_node)
 		     mark it addressable.  */
 		  if (!allows_reg && allows_mem)
 		    {
-		      STRIP_NOPS (input);
+		      input = remove_conversions (input, false);
 		      if (TREE_CODE (input) == CONST_DECL
 			  && DECL_CONST_CORRESPONDING_VAR (input))
 			input = DECL_CONST_CORRESPONDING_VAR (input);
diff --git a/gcc/ada/gcc-interface/utils.c b/gcc/ada/gcc-interface/utils.c
index c4cfde7e4215..272c192dbeec 100644
--- a/gcc/ada/gcc-interface/utils.c
+++ b/gcc/ada/gcc-interface/utils.c
@@ -1147,11 +1147,11 @@ compute_related_constant (tree op0, tree op1)
 static tree
 split_plus (tree in, tree *pvar)
 {
-  /* Strip NOPS in order to ease the tree traversal and maximize the
-     potential for constant or plus/minus discovery. We need to be careful
+  /* Strip conversions in order to ease the tree traversal and maximize the
+     potential for constant or plus/minus discovery.  We need to be careful
      to always return and set *pvar to bitsizetype trees, but it's worth
      the effort.  */
-  STRIP_NOPS (in);
+  in = remove_conversions (in, false);
 
   *pvar = convert (bitsizetype, in);
 
@@ -2288,7 +2288,9 @@ max_size (tree exp, bool max_p)
       switch (TREE_CODE_LENGTH (code))
 	{
 	case 1:
-	  if (code == NON_LVALUE_EXPR)
+	  if (code == SAVE_EXPR)
+	    return exp;
+	  else if (code == NON_LVALUE_EXPR)
 	    return max_size (TREE_OPERAND (exp, 0), max_p);
 	  else
 	    return
@@ -2330,9 +2332,7 @@ max_size (tree exp, bool max_p)
 	  }
 
 	case 3:
-	  if (code == SAVE_EXPR)
-	    return exp;
-	  else if (code == COND_EXPR)
+	  if (code == COND_EXPR)
 	    return fold_build2 (max_p ? MAX_EXPR : MIN_EXPR, type,
 				max_size (TREE_OPERAND (exp, 1), max_p),
 				max_size (TREE_OPERAND (exp, 2), max_p));
@@ -4359,8 +4359,9 @@ remove_conversions (tree exp, bool true_address)
 	return remove_conversions (TREE_OPERAND (exp, 0), true_address);
       break;
 
-    case VIEW_CONVERT_EXPR:  case NON_LVALUE_EXPR:
     CASE_CONVERT:
+    case VIEW_CONVERT_EXPR:
+    case NON_LVALUE_EXPR:
       return remove_conversions (TREE_OPERAND (exp, 0), true_address);
 
     default:
diff --git a/gcc/ada/gcc-interface/utils2.c b/gcc/ada/gcc-interface/utils2.c
index 4679ea85f309..10d12ef7ea30 100644
--- a/gcc/ada/gcc-interface/utils2.c
+++ b/gcc/ada/gcc-interface/utils2.c
@@ -1277,13 +1277,8 @@ build_unary_op (enum tree_code op_code, tree result_type, tree operand)
 
     case INDIRECT_REF:
       {
-	bool can_never_be_null;
-	tree t = operand;
-
-	while (CONVERT_EXPR_P (t) || TREE_CODE (t) == VIEW_CONVERT_EXPR)
-	  t = TREE_OPERAND (t, 0);
-
-	can_never_be_null = DECL_P (t) && DECL_CAN_NEVER_BE_NULL_P (t);
+	tree t = remove_conversions (operand, false);
+	bool can_never_be_null = DECL_P (t) && DECL_CAN_NEVER_BE_NULL_P (t);
 
 	/* If TYPE is a thin pointer, first convert to the fat pointer.  */
 	if (TYPE_IS_THIN_POINTER_P (type)
@@ -2608,16 +2603,13 @@ gnat_invariant_expr (tree expr)
 {
   tree type = TREE_TYPE (expr), t;
 
-  STRIP_NOPS (expr);
+  expr = remove_conversions (expr, false);
 
   while ((TREE_CODE (expr) == CONST_DECL
 	  || (TREE_CODE (expr) == VAR_DECL && TREE_READONLY (expr)))
 	 && decl_function_context (expr) == current_function_decl
 	 && DECL_INITIAL (expr))
-    {
-      expr = DECL_INITIAL (expr);
-      STRIP_NOPS (expr);
-    }
+    expr = remove_conversions (DECL_INITIAL (expr), false);
 
   if (TREE_CONSTANT (expr))
     return fold_convert (type, expr);
-- 
GitLab