From a441447f7f6495bb8a8e6d160d7c095da787e708 Mon Sep 17 00:00:00 2001
From: Olivier Hainque <hainque@adacore.com>
Date: Fri, 23 Jun 2006 16:18:49 +0000
Subject: [PATCH] tree.c (max_int_size_in_bytes): New function, inspired from
 code in function.c:assign_temp.

        * tree.c (max_int_size_in_bytes): New function, inspired from
        code in function.c:assign_temp.
        * tree.h (max_int_size_in_bytes): Declare.
        * function.c (assign_temp): Use it.
        * gimplify.c (create_tmp_var): Relax the assertions on the type
        properties, not mandating constant size any more.
        (force_constant_size): New static function.
        (gimple_add_tmp_var): Use it, forcing variable size to a
        constant upper bound if it is not constant on entry.

        * ada/misc.c (gnat_type_max_size): Look at TYPE_ADA_SIZE if we have
        not been able to get a constant upper bound from TYPE_SIZE_UNIT.

	* gnat.dg/varsize_temp.adb: New test.

From-SVN: r114938
---
 gcc/ChangeLog                          | 15 ++++++++++
 gcc/ada/misc.c                         | 35 +++++++++++++++++++---
 gcc/function.c                         | 19 +++---------
 gcc/gimplify.c                         | 40 +++++++++++++++++++++++---
 gcc/testsuite/ChangeLog                |  4 +++
 gcc/testsuite/gnat.dg/varsize_temp.adb | 29 +++++++++++++++++++
 gcc/tree.c                             | 33 +++++++++++++++++++++
 gcc/tree.h                             |  1 +
 8 files changed, 153 insertions(+), 23 deletions(-)
 create mode 100644 gcc/testsuite/gnat.dg/varsize_temp.adb

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index b3c1fe3a0b83..508ee05d8c18 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,18 @@
+2006-06-23  Olivier Hainque  <hainque@adacore.com>
+
+	* tree.c (max_int_size_in_bytes): New function, inspired from
+	code in function.c:assign_temp.
+	* tree.h (max_int_size_in_bytes): Declare.
+	* function.c (assign_temp): Use it.
+	* gimplify.c (create_tmp_var): Relax the assertions on the type
+	properties, not mandating constant size any more.
+	(force_constant_size): New static function.
+	(gimple_add_tmp_var): Use it, forcing variable size to a
+	constant upper bound if it is not constant on entry.
+
+	* ada/misc.c (gnat_type_max_size): Look at TYPE_ADA_SIZE if we have
+	not been able to get a constant upper bound from TYPE_SIZE_UNIT.
+
 2006-06-23  Danny Smith   <dannysmith@users.sourceforge.net>
 
 	PR target/27789
diff --git a/gcc/ada/misc.c b/gcc/ada/misc.c
index 2f68e42b4d91..47206da7e869 100644
--- a/gcc/ada/misc.c
+++ b/gcc/ada/misc.c
@@ -745,13 +745,40 @@ gnat_get_alias_set (tree type)
   return -1;
 }
 
-/* GNU_TYPE is a type.  Return its maxium size in bytes, if known.  */
+/* GNU_TYPE is a type.  Return its maxium size in bytes, if known,
+   as a constant when possible.  */
 
 static tree
-gnat_type_max_size (gnu_type)
-     tree gnu_type;
+gnat_type_max_size (tree gnu_type)
 {
-  return max_size (TYPE_SIZE_UNIT (gnu_type), true);
+  /* First see what we can get from TYPE_SIZE_UNIT, which might not be
+     constant even for simple expressions if it has already been gimplified
+     and replaced by a VAR_DECL.  */
+
+  tree max_unitsize = max_size (TYPE_SIZE_UNIT (gnu_type), true);
+
+  /* If we don't have a constant, see what we can get from TYPE_ADA_SIZE,
+     typically not gimplified.  */
+
+  if (!host_integerp (max_unitsize, 1)
+      && (TREE_CODE (gnu_type) == RECORD_TYPE
+	  || TREE_CODE (gnu_type) == UNION_TYPE
+	  || TREE_CODE (gnu_type) == QUAL_UNION_TYPE)
+      && TYPE_ADA_SIZE (gnu_type))
+    {
+      tree max_adasize = max_size (TYPE_ADA_SIZE (gnu_type), true);
+      
+      /* If we have succeded in finding a constant, round it up to the
+	 type's alignment and return the result in byte units.  */
+
+      if (host_integerp (max_adasize, 1))
+	max_unitsize
+	  = size_binop (CEIL_DIV_EXPR,
+			round_up (max_adasize, TYPE_ALIGN (gnu_type)),
+			bitsize_unit_node);
+    }
+
+  return max_unitsize;
 }
 
 /* GNU_TYPE is a type. Determine if it should be passed by reference by
diff --git a/gcc/function.c b/gcc/function.c
index 1a495ac1a056..4f989ddf9296 100644
--- a/gcc/function.c
+++ b/gcc/function.c
@@ -821,7 +821,6 @@ assign_temp (tree type_or_decl, int keep, int memory_required,
   if (mode == BLKmode || memory_required)
     {
       HOST_WIDE_INT size = int_size_in_bytes (type);
-      tree size_tree;
       rtx tmp;
 
       /* Zero sized arrays are GNU C extension.  Set size to 1 to avoid
@@ -830,20 +829,10 @@ assign_temp (tree type_or_decl, int keep, int memory_required,
 	size = 1;
 
       /* Unfortunately, we don't yet know how to allocate variable-sized
-	 temporaries.  However, sometimes we have a fixed upper limit on
-	 the size (which is stored in TYPE_ARRAY_MAX_SIZE) and can use that
-	 instead.  This is the case for Chill variable-sized strings.  */
-      if (size == -1 && TREE_CODE (type) == ARRAY_TYPE
-	  && TYPE_ARRAY_MAX_SIZE (type) != NULL_TREE
-	  && host_integerp (TYPE_ARRAY_MAX_SIZE (type), 1))
-	size = tree_low_cst (TYPE_ARRAY_MAX_SIZE (type), 1);
-
-      /* If we still haven't been able to get a size, see if the language
-	 can compute a maximum size.  */
-      if (size == -1
-	  && (size_tree = lang_hooks.types.max_size (type)) != 0
-	  && host_integerp (size_tree, 1))
-	size = tree_low_cst (size_tree, 1);
+	 temporaries.  However, sometimes we can find a fixed upper limit on
+	 the size, so try that instead.  */
+      else if (size == -1)
+	size = max_int_size_in_bytes (type);
 
       /* The size of the temporary may be too large to fit into an integer.  */
       /* ??? Not sure this should happen except for user silliness, so limit
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index 08c5caa63d9f..965c5f2fa3cc 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -479,10 +479,12 @@ create_tmp_var (tree type, const char *prefix)
   tree tmp_var;
 
   /* We don't allow types that are addressable (meaning we can't make copies),
-     incomplete, or of variable size.  */
-  gcc_assert (!TREE_ADDRESSABLE (type)
-	      && COMPLETE_TYPE_P (type)
-	      && TREE_CODE (TYPE_SIZE_UNIT (type)) == INTEGER_CST);
+     or incomplete.  We also used to reject every variable size objects here,
+     but now support those for which a constant upper bound can be obtained.
+     The processing for variable sizes is performed in gimple_add_tmp_var,
+     point at which it really matters and possibly reached via paths not going
+     through this function, e.g. after direct calls to create_tmp_var_raw.  */
+  gcc_assert (!TREE_ADDRESSABLE (type) && COMPLETE_TYPE_P (type));
 
   tmp_var = create_tmp_var_raw (type, prefix);
   gimple_add_tmp_var (tmp_var);
@@ -688,11 +690,41 @@ declare_vars (tree vars, tree scope, bool debug_info)
     }
 }
 
+/* For VAR a VAR_DECL of variable size, try to find a constant upper bound
+   for the size and adjust DECL_SIZE/DECL_SIZE_UNIT accordingly.  Abort if
+   no such upper bound can be obtained.  */
+
+static void
+force_constant_size (tree var)
+{
+  /* The only attempt we make is by querying the maximum size of objects
+     of the variable's type.  */
+
+  HOST_WIDE_INT max_size;
+
+  gcc_assert (TREE_CODE (var) == VAR_DECL);
+
+  max_size = max_int_size_in_bytes (TREE_TYPE (var));
+
+  gcc_assert (max_size >= 0);
+
+  DECL_SIZE_UNIT (var)
+    = build_int_cst (TREE_TYPE (DECL_SIZE_UNIT (var)), max_size);
+  DECL_SIZE (var)
+    = build_int_cst (TREE_TYPE (DECL_SIZE (var)), max_size * BITS_PER_UNIT);
+}
+
 void
 gimple_add_tmp_var (tree tmp)
 {
   gcc_assert (!TREE_CHAIN (tmp) && !DECL_SEEN_IN_BIND_EXPR_P (tmp));
 
+  /* Later processing assumes that the object size is constant, which might
+     not be true at this point.  Force the use of a constant upper bound in
+     this case.  */
+  if (!host_integerp (DECL_SIZE_UNIT (tmp), 1))
+    force_constant_size (tmp);
+
   DECL_CONTEXT (tmp) = current_function_decl;
   DECL_SEEN_IN_BIND_EXPR_P (tmp) = 1;
 
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 3b3dc6bac2fc..cadfeef986d2 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,7 @@
+2006-06-23  Olivier Hainque  <hainque@adacore.com>
+
+	* gnat.dg/varsize_temp.adb: New test.
+	
 2006-06-23  Volker Reichelt  <reichelt@igpm.rwth-aachen.de>
 
 	PR c++/11468
diff --git a/gcc/testsuite/gnat.dg/varsize_temp.adb b/gcc/testsuite/gnat.dg/varsize_temp.adb
new file mode 100644
index 000000000000..b7c3a0b60397
--- /dev/null
+++ b/gcc/testsuite/gnat.dg/varsize_temp.adb
@@ -0,0 +1,29 @@
+-- { dg-do compile }
+
+procedure Varsize_Temp (Nbytes : Natural) is
+
+   type Message_T (Length : Natural) is record
+      case Length is
+         when 0 => null;
+         when others => Id : Natural;
+      end case;
+   end record;
+
+   type Local_Message_T is new Message_T (Nbytes);
+
+   function One_message return Local_Message_T is
+      M : Local_Message_T;
+   begin
+      if M.Length > 0 then
+         M.Id := 1;
+      end if;
+      return M;
+   end;
+
+   procedure Process (X : Local_Message_T) is begin null; end;
+
+begin
+   Process (One_Message);
+end;
+
+
diff --git a/gcc/tree.c b/gcc/tree.c
index 2df2f7b3cb5a..cbf4cc51eed7 100644
--- a/gcc/tree.c
+++ b/gcc/tree.c
@@ -1733,6 +1733,39 @@ int_size_in_bytes (tree type)
 
   return TREE_INT_CST_LOW (t);
 }
+
+/* Return the maximum size of TYPE (in bytes) as a wide integer
+   or return -1 if the size can vary or is larger than an integer.  */
+
+HOST_WIDE_INT
+max_int_size_in_bytes (tree type)
+{
+  HOST_WIDE_INT size = -1;
+  tree size_tree;
+
+  /* If this is an array type, check for a possible MAX_SIZE attached.  */
+
+  if (TREE_CODE (type) == ARRAY_TYPE)
+    {
+      size_tree = TYPE_ARRAY_MAX_SIZE (type);
+
+      if (size_tree && host_integerp (size_tree, 1))
+	size = tree_low_cst (size_tree, 1);
+    }
+
+  /* If we still haven't been able to get a size, see if the language
+     can compute a maximum size.  */
+
+  if (size == -1)
+    {
+      size_tree = lang_hooks.types.max_size (type);
+
+      if (size_tree && host_integerp (size_tree, 1))
+	size = tree_low_cst (size_tree, 1);
+    }
+
+  return size;
+}
 
 /* Return the bit position of FIELD, in bits from the start of the record.
    This is a tree of type bitsizetype.  */
diff --git a/gcc/tree.h b/gcc/tree.h
index ad21877733a2..6d8ad6aac5cd 100644
--- a/gcc/tree.h
+++ b/gcc/tree.h
@@ -3833,6 +3833,7 @@ extern tree expr_last (tree);
 extern tree expr_only (tree);
 extern tree size_in_bytes (tree);
 extern HOST_WIDE_INT int_size_in_bytes (tree);
+extern HOST_WIDE_INT max_int_size_in_bytes (tree);
 extern tree bit_position (tree);
 extern HOST_WIDE_INT int_bit_position (tree);
 extern tree byte_position (tree);
-- 
GitLab