From daf8c6f03b7b7ae33e2e8e301d367eb8cce80e5c Mon Sep 17 00:00:00 2001
From: Daniel Franke <franke.daniel@gmail.com>
Date: Wed, 19 May 2010 12:35:34 -0400
Subject: [PATCH] re PR fortran/44055 (Warn (-Wconversion*) when converting
 single to double precision)

gcc/fortran/:
2010-05-19  Daniel Franke  <franke.daniel@gmail.com>

	PR fortran/44055
	* lang.opt (Wconversion-extra): New option.
	* gfortran.h (gfc_option_t): Add warn_conversion_extra.
	* options.c (gfc_init_options): Disable -Wconversion-extra by default.
	(set_Wall): Enable -Wconversion.
	(gfc_handle_option): Set warn_conversion_extra.
	* intrinsic.c (gfc_convert_type_warn): Ignore kind conditions
	introduced for -Wconversion if -Wconversion-extra is present.
	* invoke.texi: Add -Wconversion to -Wall; document new behaviour of
	-Wconversion; document -Wconversion-extra.

gcc/testsuite/:
2010-05-19  Daniel Franke  <franke.daniel@gmail.com>

	PR fortran/44055
	* gfortran.dg/c_sizeof_2.f90: Add -Wno-conversion to dg-options;
	Fixed scope of C_SIZEOF.
	* gfortran.dg/warn_conversion_2.f90: New.

From-SVN: r159586
---
 gcc/fortran/ChangeLog                         | 13 +++++
 gcc/fortran/gfortran.h                        |  1 +
 gcc/fortran/intrinsic.c                       | 47 ++++++++++++++-----
 gcc/fortran/invoke.texi                       | 13 +++--
 gcc/fortran/lang.opt                          |  4 ++
 gcc/fortran/options.c                         |  6 +++
 gcc/testsuite/ChangeLog                       |  7 +++
 gcc/testsuite/gfortran.dg/c_sizeof_2.f90      |  7 +--
 .../gfortran.dg/warn_conversion_2.f90         |  6 +++
 9 files changed, 86 insertions(+), 18 deletions(-)
 create mode 100644 gcc/testsuite/gfortran.dg/warn_conversion_2.f90

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 771a2639f25e..0d8fa4373481 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,16 @@
+2010-05-19  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/44055
+	* lang.opt (Wconversion-extra): New option.
+	* gfortran.h (gfc_option_t): Add warn_conversion_extra.
+	* options.c (gfc_init_options): Disable -Wconversion-extra by default.
+	(set_Wall): Enable -Wconversion.
+	(gfc_handle_option): Set warn_conversion_extra.
+	* intrinsic.c (gfc_convert_type_warn): Ignore kind conditions
+	introduced for -Wconversion if -Wconversion-extra is present.
+	* invoke.texi: Add -Wconversion to -Wall; document new behaviour of
+	-Wconversion; document -Wconversion-extra.
+
 2010-05-19  Daniel Franke  <franke.daniel@gmail.com>
 
 	PR fortran/42360
diff --git a/gcc/fortran/gfortran.h b/gcc/fortran/gfortran.h
index 903f05ca9d8a..15f2728f2285 100644
--- a/gcc/fortran/gfortran.h
+++ b/gcc/fortran/gfortran.h
@@ -2105,6 +2105,7 @@ typedef struct
   int warn_aliasing;
   int warn_ampersand;
   int warn_conversion;
+  int warn_conversion_extra;
   int warn_implicit_interface;
   int warn_implicit_procedure;
   int warn_line_truncation;
diff --git a/gcc/fortran/intrinsic.c b/gcc/fortran/intrinsic.c
index 02dea3039fd7..a92b5b54519e 100644
--- a/gcc/fortran/intrinsic.c
+++ b/gcc/fortran/intrinsic.c
@@ -4015,18 +4015,38 @@ gfc_convert_type_warn (gfc_expr *expr, gfc_typespec *ts, int eflag, int wflag)
 
   /* At this point, a conversion is necessary. A warning may be needed.  */
   if ((gfc_option.warn_std & sym->standard) != 0)
-    gfc_warning_now ("Extension: Conversion from %s to %s at %L",
-		     gfc_typename (&from_ts), gfc_typename (ts), &expr->where);
-  else if (wflag && gfc_option.warn_conversion)
     {
+      gfc_warning_now ("Extension: Conversion from %s to %s at %L",
+		       gfc_typename (&from_ts), gfc_typename (ts),
+		       &expr->where);
+    }
+  else if (wflag)
+    {
+      /* Two modes of warning:
+	  - gfc_option.warn_conversion tries to be more intelligent
+	    about the warnings raised and omits those where smaller
+	    kinds are promoted to larger ones without change in the
+	    value
+	  - gfc_option.warn_conversion_extra does not take the kinds
+	    into account and also warns for coversions like
+	    REAL(4) -> REAL(8)
+
+	 NOTE: Possible enhancement for warn_conversion
+	 If converting from a smaller to a larger kind, check if the
+	 value is constant and if yes, whether the value still fits
+	 in the smaller kind. If yes, omit the warning.
+      */
+
       /* If the types are the same (but not LOGICAL), and if from-kind
 	 is larger than to-kind, this may indicate a loss of precision.
 	 The same holds for conversions from REAL to COMPLEX.  */
       if (((from_ts.type == ts->type && from_ts.type != BT_LOGICAL)
-	     && from_ts.kind > ts->kind)
+           && ((gfc_option.warn_conversion && from_ts.kind > ts->kind)
+	       || gfc_option.warn_conversion_extra))
 	  || ((from_ts.type == BT_REAL && ts->type == BT_COMPLEX)
-	      && from_ts.kind > ts->kind))
-	gfc_warning_now ("Possible loss of precision in conversion "
+	      && ((gfc_option.warn_conversion && from_ts.kind > ts->kind)
+		  || gfc_option.warn_conversion_extra)))
+	gfc_warning_now ("Possible change of value in conversion "
 			 "from %s to %s at %L", gfc_typename (&from_ts),
 			 gfc_typename (ts), &expr->where);
 
@@ -4037,18 +4057,21 @@ gfc_convert_type_warn (gfc_expr *expr, gfc_typespec *ts, int eflag, int wflag)
 	 an overflow error with range checking. */
       else if (from_ts.type == BT_INTEGER
 	       && (ts->type == BT_REAL || ts->type == BT_COMPLEX)
-	       && from_ts.kind > ts->kind)
-	gfc_warning_now ("Possible loss of digits in conversion "
+	       && ((gfc_option.warn_conversion && from_ts.kind > ts->kind)
+		   || gfc_option.warn_conversion_extra))
+	gfc_warning_now ("Possible change of value in conversion "
 			 "from %s to %s at %L", gfc_typename (&from_ts),
 			 gfc_typename (ts), &expr->where);
 
       /* If REAL/COMPLEX is converted to INTEGER, or COMPLEX is converted
         to REAL we almost certainly have a loss of digits, regardless of
         the respective kinds.  */
-      else if (((from_ts.type == BT_REAL || from_ts.type == BT_COMPLEX)
-		 && ts->type == BT_INTEGER)
-	       || (from_ts.type == BT_COMPLEX && ts->type == BT_REAL))
-	gfc_warning_now ("Likely loss of digits in conversion from"
+      else if ((((from_ts.type == BT_REAL || from_ts.type == BT_COMPLEX)
+		  && ts->type == BT_INTEGER)
+		|| (from_ts.type == BT_COMPLEX && ts->type == BT_REAL))
+	       && (gfc_option.warn_conversion
+	           || gfc_option.warn_conversion_extra))
+	gfc_warning_now ("Possible change of value in conversion from "
 			"%s to %s at %L", gfc_typename (&from_ts),
 			gfc_typename (ts), &expr->where);
     }
diff --git a/gcc/fortran/invoke.texi b/gcc/fortran/invoke.texi
index 7b3fa6d4baf5..1b14cef8db2f 100644
--- a/gcc/fortran/invoke.texi
+++ b/gcc/fortran/invoke.texi
@@ -688,8 +688,8 @@ warnings.
 @cindex warnings, all
 Enables commonly used warning options pertaining to usage that
 we recommend avoiding and that we believe are easy to avoid.
-This currently includes @option{-Waliasing},
-@option{-Wampersand}, @option{-Wsurprising}, @option{-Wintrinsics-std},
+This currently includes @option{-Waliasing}, @option{-Wampersand}, 
+@option{-Wconversion}, @option{-Wsurprising}, @option{-Wintrinsics-std},
 @option{-Wno-tabs}, @option{-Wintrinsic-shadow} and @option{-Wline-truncation}.
 
 @item -Waliasing
@@ -746,7 +746,14 @@ Warn when a source code line will be truncated.
 @opindex @code{Wconversion}
 @cindex warnings, conversion
 @cindex conversion
-Warn about implicit conversions between different types.
+Warn about implicit conversions that are likely to change the value of 
+the expression after conversion. Implied by @option{-Wall}.
+
+@item -Wconversion-extra
+@opindex @code{Wconversion-extra}
+@cindex warnings, conversion
+@cindex conversion
+Warn about implicit conversions between different types and kinds.
 
 @item -Wimplicit-interface
 @opindex @code{Wimplicit-interface}
diff --git a/gcc/fortran/lang.opt b/gcc/fortran/lang.opt
index 1438aa2d0ca9..57ac4293351c 100644
--- a/gcc/fortran/lang.opt
+++ b/gcc/fortran/lang.opt
@@ -92,6 +92,10 @@ Wconversion
 Fortran Warning
 ; Documented in C
 
+Wconversion-extra
+Fortran Warning
+Warn about most implicit conversions
+
 Wimplicit-interface
 Fortran Warning
 Warn about calls with implicit interface
diff --git a/gcc/fortran/options.c b/gcc/fortran/options.c
index 6a5a3db6f3bd..320dc722b2c0 100644
--- a/gcc/fortran/options.c
+++ b/gcc/fortran/options.c
@@ -78,6 +78,7 @@ gfc_init_options (unsigned int argc, const char **argv)
   gfc_option.warn_character_truncation = 0;
   gfc_option.warn_array_temp = 0;
   gfc_option.warn_conversion = 0;
+  gfc_option.warn_conversion_extra = 0;
   gfc_option.warn_implicit_interface = 0;
   gfc_option.warn_line_truncation = 0;
   gfc_option.warn_surprising = 0;
@@ -402,6 +403,7 @@ set_Wall (int setting)
 {
   gfc_option.warn_aliasing = setting;
   gfc_option.warn_ampersand = setting;
+  gfc_option.warn_conversion = setting;
   gfc_option.warn_line_truncation = setting;
   gfc_option.warn_surprising = setting;
   gfc_option.warn_tabs = !setting;
@@ -568,6 +570,10 @@ gfc_handle_option (size_t scode, const char *arg, int value,
       gfc_option.warn_conversion = value;
       break;
 
+    case OPT_Wconversion_extra:
+      gfc_option.warn_conversion_extra = value;
+      break;
+
     case OPT_Wimplicit_interface:
       gfc_option.warn_implicit_interface = value;
       break;
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index d68e7c6f34a5..84c0dd71d1b8 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,10 @@
+2010-05-19  Daniel Franke  <franke.daniel@gmail.com>
+
+	PR fortran/44055
+	* gfortran.dg/c_sizeof_2.f90: Add -Wno-conversion to dg-options;
+	Fixed scope of C_SIZEOF.
+	* gfortran.dg/warn_conversion_2.f90: New.
+
 2010-05-19  Rainer Orth  <ro@CeBiTec.Uni-Bielefeld.DE>
 
 	* lib/target-supports.exp (check_effective_target_sse2): New proc.
diff --git a/gcc/testsuite/gfortran.dg/c_sizeof_2.f90 b/gcc/testsuite/gfortran.dg/c_sizeof_2.f90
index 6e32cb34687e..fb65adce5f0e 100644
--- a/gcc/testsuite/gfortran.dg/c_sizeof_2.f90
+++ b/gcc/testsuite/gfortran.dg/c_sizeof_2.f90
@@ -1,8 +1,9 @@
 ! { dg-do compile }
-! { dg-options "-std=f2003 -Wall" }
+! { dg-options "-std=f2003 -Wall -Wno-conversion" }
 ! Support F2008's c_sizeof()
 !
-integer(4) :: i
-i = c_sizeof(i) ! { dg-warning "Fortran 2008" }
+USE ISO_C_BINDING
+integer(C_SIZE_T) :: i
+i = c_sizeof(i)           ! { dg-warning "Fortran 2008" }
 end
 
diff --git a/gcc/testsuite/gfortran.dg/warn_conversion_2.f90 b/gcc/testsuite/gfortran.dg/warn_conversion_2.f90
new file mode 100644
index 000000000000..cb3b760a5e2b
--- /dev/null
+++ b/gcc/testsuite/gfortran.dg/warn_conversion_2.f90
@@ -0,0 +1,6 @@
+! { dg-do "compile" }
+! { dg-options "-Wconversion-extra" }
+
+  real(8) :: sqrt2
+  sqrt2 = sqrt(2.0)      ! { dg-warning "conversion" }
+end
-- 
GitLab