From 1a33dc9ec24fed0406de07f54e0442915e3cfedb Mon Sep 17 00:00:00 2001
From: Uros Bizjak <ubizjak@gmail.com>
Date: Wed, 31 Dec 2014 15:50:10 +0100
Subject: [PATCH] trans-array.c (trans_array_bound_check): Use xasprintf
 instead of unchecked asprintf.

	* trans-array.c (trans_array_bound_check): Use xasprintf instead
	of unchecked asprintf.
	(gfc_conv_array_ref): Ditto.
	(gfc_conv_ss_startstride): Ditto.
	(gfc_trans_dummy_array_bias): Ditto.
	(gfc_conv_array_parameter): Ditto.
	* trans-decl.c (gfc_generate_function_code): Ditto.
	* trans-expr.c (gfc_conv_substring): Ditto.
	(gfc_conv_procedure_call): Ditto.
	* trans-io.c (gfc_trans_io_runtime_check): Ditto.
	(set_string): Ditto.
	* trans.c (trans-runtime_error_vararg): Ditto.

From-SVN: r219126
---
 gcc/fortran/ChangeLog     | 15 +++++++++
 gcc/fortran/trans-array.c | 68 +++++++++++++++++++--------------------
 gcc/fortran/trans-decl.c  |  4 +--
 gcc/fortran/trans-expr.c  | 45 +++++++++++++-------------
 gcc/fortran/trans-io.c    |  6 ++--
 gcc/fortran/trans.c       | 10 +++---
 6 files changed, 82 insertions(+), 66 deletions(-)

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 3329c42347d1..10ad0bf2a354 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,18 @@
+2014-12-31  Uros Bizjak  <ubizjak@gmail.com>
+
+	* trans-array.c (trans_array_bound_check): Use xasprintf instead
+	of unchecked asprintf.
+	(gfc_conv_array_ref): Ditto.
+	(gfc_conv_ss_startstride): Ditto.
+	(gfc_trans_dummy_array_bias): Ditto.
+	(gfc_conv_array_parameter): Ditto.
+	* trans-decl.c (gfc_generate_function_code): Ditto.
+	* trans-expr.c (gfc_conv_substring): Ditto.
+	(gfc_conv_procedure_call): Ditto.
+	* trans-io.c (gfc_trans_io_runtime_check): Ditto.
+	(set_string): Ditto.
+	* trans.c (trans-runtime_error_vararg): Ditto.
+
 2014-12-29  Janus Weil  <janus@gcc.gnu.org>
 
 	PR fortran/60357
diff --git a/gcc/fortran/trans-array.c b/gcc/fortran/trans-array.c
index ebd7f11a53bb..07a9873be861 100644
--- a/gcc/fortran/trans-array.c
+++ b/gcc/fortran/trans-array.c
@@ -2799,11 +2799,11 @@ trans_array_bound_check (gfc_se * se, gfc_ss *ss, tree index, int n,
       tmp_up = gfc_conv_array_ubound (descriptor, n);
 
       if (name)
-	asprintf (&msg, "Index '%%ld' of dimension %d of array '%s' "
-		  "outside of expected range (%%ld:%%ld)", n+1, name);
+	msg = xasprintf ("Index '%%ld' of dimension %d of array '%s' "
+			 "outside of expected range (%%ld:%%ld)", n+1, name);
       else
-	asprintf (&msg, "Index '%%ld' of dimension %d "
-		  "outside of expected range (%%ld:%%ld)", n+1);
+	msg = xasprintf ("Index '%%ld' of dimension %d "
+			 "outside of expected range (%%ld:%%ld)", n+1);
 
       fault = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
 			       index, tmp_lo);
@@ -2824,11 +2824,11 @@ trans_array_bound_check (gfc_se * se, gfc_ss *ss, tree index, int n,
       tmp_lo = gfc_conv_array_lbound (descriptor, n);
 
       if (name)
-	asprintf (&msg, "Index '%%ld' of dimension %d of array '%s' "
-		  "below lower bound of %%ld", n+1, name);
+	msg = xasprintf ("Index '%%ld' of dimension %d of array '%s' "
+			 "below lower bound of %%ld", n+1, name);
       else
-	asprintf (&msg, "Index '%%ld' of dimension %d "
-		  "below lower bound of %%ld", n+1);
+	msg = xasprintf ("Index '%%ld' of dimension %d "
+			 "below lower bound of %%ld", n+1);
 
       fault = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
 			       index, tmp_lo);
@@ -3259,8 +3259,8 @@ gfc_conv_array_ref (gfc_se * se, gfc_array_ref * ar, gfc_expr *expr,
 
 	  cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
 				  indexse.expr, tmp);
-	  asprintf (&msg, "Index '%%ld' of dimension %d of array '%s' "
-		    "below lower bound of %%ld", n+1, var_name);
+	  msg = xasprintf ("Index '%%ld' of dimension %d of array '%s' "
+			   "below lower bound of %%ld", n+1, var_name);
 	  gfc_trans_runtime_check (true, false, cond, &se->pre, where, msg,
 				   fold_convert (long_integer_type_node,
 						 indexse.expr),
@@ -3283,8 +3283,8 @@ gfc_conv_array_ref (gfc_se * se, gfc_array_ref * ar, gfc_expr *expr,
 
 	      cond = fold_build2_loc (input_location, GT_EXPR,
 				      boolean_type_node, indexse.expr, tmp);
-	      asprintf (&msg, "Index '%%ld' of dimension %d of array '%s' "
-			"above upper bound of %%ld", n+1, var_name);
+	      msg = xasprintf ("Index '%%ld' of dimension %d of array '%s' "
+			       "above upper bound of %%ld", n+1, var_name);
 	      gfc_trans_runtime_check (true, false, cond, &se->pre, where, msg,
 				   fold_convert (long_integer_type_node,
 						 indexse.expr),
@@ -3981,8 +3981,8 @@ done:
 	      /* Zero stride is not allowed.  */
 	      tmp = fold_build2_loc (input_location, EQ_EXPR, boolean_type_node,
 				     info->stride[dim], gfc_index_zero_node);
-	      asprintf (&msg, "Zero stride is not allowed, for dimension %d "
-			"of array '%s'", dim + 1, expr_name);
+	      msg = xasprintf ("Zero stride is not allowed, for dimension %d "
+			       "of array '%s'", dim + 1, expr_name);
 	      gfc_trans_runtime_check (true, false, tmp, &inner,
 				       expr_loc, msg);
 	      free (msg);
@@ -4039,9 +4039,9 @@ done:
 		  tmp2 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
 					  boolean_type_node,
 					  non_zerosized, tmp2);
-		  asprintf (&msg, "Index '%%ld' of dimension %d of array '%s' "
-			    "outside of expected range (%%ld:%%ld)",
-			    dim + 1, expr_name);
+		  msg = xasprintf ("Index '%%ld' of dimension %d of array '%s' "
+				   "outside of expected range (%%ld:%%ld)",
+				   dim + 1, expr_name);
 		  gfc_trans_runtime_check (true, false, tmp, &inner,
 					   expr_loc, msg,
 		     fold_convert (long_integer_type_node, info->start[dim]),
@@ -4061,9 +4061,9 @@ done:
 					 info->start[dim], lbound);
 		  tmp = fold_build2_loc (input_location, TRUTH_AND_EXPR,
 					 boolean_type_node, non_zerosized, tmp);
-		  asprintf (&msg, "Index '%%ld' of dimension %d of array '%s' "
-			    "below lower bound of %%ld",
-			    dim + 1, expr_name);
+		  msg = xasprintf ("Index '%%ld' of dimension %d of array '%s' "
+				   "below lower bound of %%ld",
+				   dim + 1, expr_name);
 		  gfc_trans_runtime_check (true, false, tmp, &inner,
 					   expr_loc, msg,
 		     fold_convert (long_integer_type_node, info->start[dim]),
@@ -4093,9 +4093,9 @@ done:
 					  boolean_type_node, tmp, ubound);
 		  tmp3 = fold_build2_loc (input_location, TRUTH_AND_EXPR,
 					  boolean_type_node, non_zerosized, tmp3);
-		  asprintf (&msg, "Index '%%ld' of dimension %d of array '%s' "
-			    "outside of expected range (%%ld:%%ld)",
-			    dim + 1, expr_name);
+		  msg = xasprintf ("Index '%%ld' of dimension %d of array '%s' "
+				   "outside of expected range (%%ld:%%ld)",
+				   dim + 1, expr_name);
 		  gfc_trans_runtime_check (true, false, tmp2, &inner,
 					   expr_loc, msg,
 		     fold_convert (long_integer_type_node, tmp),
@@ -4110,9 +4110,9 @@ done:
 		}
 	      else
 		{
-		  asprintf (&msg, "Index '%%ld' of dimension %d of array '%s' "
-			    "below lower bound of %%ld",
-			    dim + 1, expr_name);
+		  msg = xasprintf ("Index '%%ld' of dimension %d of array '%s' "
+				   "below lower bound of %%ld",
+				   dim + 1, expr_name);
 		  gfc_trans_runtime_check (true, false, tmp2, &inner,
 					   expr_loc, msg,
 		     fold_convert (long_integer_type_node, tmp),
@@ -4139,9 +4139,9 @@ done:
 		{
 		  tmp3 = fold_build2_loc (input_location, NE_EXPR,
 					  boolean_type_node, tmp, size[n]);
-		  asprintf (&msg, "Array bound mismatch for dimension %d "
-			    "of array '%s' (%%ld/%%ld)",
-			    dim + 1, expr_name);
+		  msg = xasprintf ("Array bound mismatch for dimension %d "
+				   "of array '%s' (%%ld/%%ld)",
+				   dim + 1, expr_name);
 
 		  gfc_trans_runtime_check (true, false, tmp3, &inner,
 					   expr_loc, msg,
@@ -6013,8 +6013,8 @@ gfc_trans_dummy_array_bias (gfc_symbol * sym, tree tmpdesc,
 					 gfc_index_one_node, stride2);
 	      tmp = fold_build2_loc (input_location, NE_EXPR,
 				     gfc_array_index_type, temp, stride2);
-	      asprintf (&msg, "Dimension %d of array '%s' has extent "
-			"%%ld instead of %%ld", n+1, sym->name);
+	      msg = xasprintf ("Dimension %d of array '%s' has extent "
+			       "%%ld instead of %%ld", n+1, sym->name);
 
 	      gfc_trans_runtime_check (true, false, tmp, &init, &loc, msg,
 			fold_convert (long_integer_type_node, temp),
@@ -7292,10 +7292,10 @@ gfc_conv_array_parameter (gfc_se * se, gfc_expr * expr, bool g77,
 	  char * msg;
 
 	  if (fsym && proc_name)
-	    asprintf (&msg, "An array temporary was created for argument "
-		      "'%s' of procedure '%s'", fsym->name, proc_name);
+	    msg = xasprintf ("An array temporary was created for argument "
+			     "'%s' of procedure '%s'", fsym->name, proc_name);
 	  else
-	    asprintf (&msg, "An array temporary was created");
+	    msg = xasprintf ("An array temporary was created");
 
 	  tmp = build_fold_indirect_ref_loc (input_location,
 					 desc);
diff --git a/gcc/fortran/trans-decl.c b/gcc/fortran/trans-decl.c
index 494d8aa905eb..75b84f1495bb 100644
--- a/gcc/fortran/trans-decl.c
+++ b/gcc/fortran/trans-decl.c
@@ -5723,8 +5723,8 @@ gfc_generate_function_code (gfc_namespace * ns)
     {
       char * msg;
 
-      asprintf (&msg, "Recursive call to nonrecursive procedure '%s'",
-		sym->name);
+      msg = xasprintf ("Recursive call to nonrecursive procedure '%s'",
+		       sym->name);
       recurcheckvar = gfc_create_var (boolean_type_node, "is_recursive");
       TREE_STATIC (recurcheckvar) = 1;
       DECL_INITIAL (recurcheckvar) = boolean_false_node;
diff --git a/gcc/fortran/trans-expr.c b/gcc/fortran/trans-expr.c
index 3793cfb0d927..85c77b735ea6 100644
--- a/gcc/fortran/trans-expr.c
+++ b/gcc/fortran/trans-expr.c
@@ -1799,11 +1799,11 @@ gfc_conv_substring (gfc_se * se, gfc_ref * ref, int kind,
       fault = fold_build2_loc (input_location, TRUTH_ANDIF_EXPR,
 			       boolean_type_node, nonempty, fault);
       if (name)
-	asprintf (&msg, "Substring out of bounds: lower bound (%%ld) of '%s' "
-		  "is less than one", name);
+	msg = xasprintf ("Substring out of bounds: lower bound (%%ld) of '%s' "
+			 "is less than one", name);
       else
-	asprintf (&msg, "Substring out of bounds: lower bound (%%ld)"
-		  "is less than one");
+	msg = xasprintf ("Substring out of bounds: lower bound (%%ld)"
+			 "is less than one");
       gfc_trans_runtime_check (true, false, fault, &se->pre, where, msg,
 			       fold_convert (long_integer_type_node,
 					     start.expr));
@@ -1815,11 +1815,11 @@ gfc_conv_substring (gfc_se * se, gfc_ref * ref, int kind,
       fault = fold_build2_loc (input_location, TRUTH_ANDIF_EXPR,
 			       boolean_type_node, nonempty, fault);
       if (name)
-	asprintf (&msg, "Substring out of bounds: upper bound (%%ld) of '%s' "
-		  "exceeds string length (%%ld)", name);
+	msg = xasprintf ("Substring out of bounds: upper bound (%%ld) of '%s' "
+			 "exceeds string length (%%ld)", name);
       else
-	asprintf (&msg, "Substring out of bounds: upper bound (%%ld) "
-		  "exceeds string length (%%ld)");
+	msg = xasprintf ("Substring out of bounds: upper bound (%%ld) "
+			 "exceeds string length (%%ld)");
       gfc_trans_runtime_check (true, false, fault, &se->pre, where, msg,
 			       fold_convert (long_integer_type_node, end.expr),
 			       fold_convert (long_integer_type_node,
@@ -4930,18 +4930,19 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
 
 	      if (attr.allocatable
 		  && (fsym == NULL || !fsym->attr.allocatable))
-		asprintf (&msg, "Allocatable actual argument '%s' is not "
-			  "allocated or not present", e->symtree->n.sym->name);
+		msg = xasprintf ("Allocatable actual argument '%s' is not "
+				 "allocated or not present",
+				 e->symtree->n.sym->name);
 	      else if (attr.pointer
 		       && (fsym == NULL || !fsym->attr.pointer))
-		asprintf (&msg, "Pointer actual argument '%s' is not "
-			  "associated or not present",
-			  e->symtree->n.sym->name);
+		msg = xasprintf ("Pointer actual argument '%s' is not "
+				 "associated or not present",
+				 e->symtree->n.sym->name);
 	      else if (attr.proc_pointer
 		       && (fsym == NULL || !fsym->attr.proc_pointer))
-		asprintf (&msg, "Proc-pointer actual argument '%s' is not "
-			  "associated or not present",
-			  e->symtree->n.sym->name);
+		msg = xasprintf ("Proc-pointer actual argument '%s' is not "
+				 "associated or not present",
+				 e->symtree->n.sym->name);
 	      else
 		goto end_pointer_check;
 
@@ -4963,16 +4964,16 @@ gfc_conv_procedure_call (gfc_se * se, gfc_symbol * sym,
 	    {
 	      if (attr.allocatable
 		  && (fsym == NULL || !fsym->attr.allocatable))
-		asprintf (&msg, "Allocatable actual argument '%s' is not "
-		      "allocated", e->symtree->n.sym->name);
+		msg = xasprintf ("Allocatable actual argument '%s' is not "
+				 "allocated", e->symtree->n.sym->name);
 	      else if (attr.pointer
 		       && (fsym == NULL || !fsym->attr.pointer))
-		asprintf (&msg, "Pointer actual argument '%s' is not "
-		      "associated", e->symtree->n.sym->name);
+		msg = xasprintf ("Pointer actual argument '%s' is not "
+				 "associated", e->symtree->n.sym->name);
 	      else if (attr.proc_pointer
 		       && (fsym == NULL || !fsym->attr.proc_pointer))
-		asprintf (&msg, "Proc-pointer actual argument '%s' is not "
-		      "associated", e->symtree->n.sym->name);
+		msg = xasprintf ("Proc-pointer actual argument '%s' is not "
+				 "associated", e->symtree->n.sym->name);
 	      else
 		goto end_pointer_check;
 
diff --git a/gcc/fortran/trans-io.c b/gcc/fortran/trans-io.c
index e1b7eb9d10e6..3ef223b4b204 100644
--- a/gcc/fortran/trans-io.c
+++ b/gcc/fortran/trans-io.c
@@ -258,7 +258,7 @@ gfc_trans_io_runtime_check (bool has_iostat, tree cond, tree var,
 
   arg2 = build_int_cst (integer_type_node, error_code),
 
-  asprintf (&message, "%s", _(msgid));
+  message = xasprintf ("%s", _(msgid));
   arg3 = gfc_build_addr_expr (pchar_type_node,
 			      gfc_build_localized_cstring_const (message));
   free (message);
@@ -715,8 +715,8 @@ set_string (stmtblock_t * block, stmtblock_t * postblock, tree var,
       cond = fold_build2_loc (input_location, LT_EXPR, boolean_type_node,
 			      tmp, build_int_cst (TREE_TYPE (tmp), 0));
 
-      asprintf(&msg, "Label assigned to variable '%s' (%%ld) is not a format "
-	       "label", e->symtree->name);
+      msg = xasprintf ("Label assigned to variable '%s' (%%ld) is not a format "
+		       "label", e->symtree->name);
       gfc_trans_runtime_check (true, false, cond, &se.pre, &e->where, msg,
 			       fold_convert (long_integer_type_node, tmp));
       free (msg);
diff --git a/gcc/fortran/trans.c b/gcc/fortran/trans.c
index 7c54b8e24997..af6830c64b8d 100644
--- a/gcc/fortran/trans.c
+++ b/gcc/fortran/trans.c
@@ -418,18 +418,18 @@ trans_runtime_error_vararg (bool error, locus* where, const char* msgid,
   if (where)
     {
       line = LOCATION_LINE (where->lb->location);
-      asprintf (&message, "At line %d of file %s",  line,
-		where->lb->file->filename);
+      message = xasprintf ("At line %d of file %s",  line,
+			   where->lb->file->filename);
     }
   else
-    asprintf (&message, "In file '%s', around line %d",
-	      gfc_source_file, LOCATION_LINE (input_location) + 1);
+    message = xasprintf ("In file '%s', around line %d",
+			 gfc_source_file, LOCATION_LINE (input_location) + 1);
 
   arg = gfc_build_addr_expr (pchar_type_node,
 			     gfc_build_localized_cstring_const (message));
   free (message);
 
-  asprintf (&message, "%s", _(msgid));
+  message = xasprintf ("%s", _(msgid));
   arg2 = gfc_build_addr_expr (pchar_type_node,
 			      gfc_build_localized_cstring_const (message));
   free (message);
-- 
GitLab