From 3aa34c1d8f94fc56d66de3b8d09dbd8c2c9e8525 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Manuel=20L=C3=B3pez-Ib=C3=A1=C3=B1ez?= <manu@gcc.gnu.org>
Date: Tue, 11 Nov 2014 22:50:48 +0000
Subject: [PATCH] re PR fortran/44054 (Handle -Werror, -Werror=,
 -fdiagnostics-show-option, !GCC$ diagnostic (pragmas) and color)
MIME-Version: 1.0
Content-Type: text/plain; charset=UTF-8
Content-Transfer-Encoding: 8bit

libcpp/ChangeLog:

2014-11-11  Manuel López-Ibáñez  <manu@gcc.gnu.org>

	PR fortran/44054
	* include/line-map.h (linemap_position_for_loc_and_offset):
	Declare.
	* line-map.c (linemap_position_for_loc_and_offset): New.


gcc/fortran/ChangeLog:

2014-11-11  Manuel López-Ibáñez  <manu@gcc.gnu.org>

	PR fortran/44054
	* gfortran.h (warn_use_without_only): Remove.
	(gfc_diagnostics_finish): Declare.
	* error.c: Include tree-diagnostics.h
	(gfc_format_decoder): New.
	(gfc_diagnostics_init): Use gfc_format_decoder. Set default caret
	char.
	(gfc_diagnostics_finish): Restore tree diagnostics defaults, but
	keep gfc_diagnostics_starter and finalizer. Restore default caret.
	* options.c: Remove all uses of warn_use_without_only.
	* lang.opt (Wuse-without-only): Add Var.
	* f95-lang.c (gfc_be_parse_file): Call gfc_diagnostics_finish.
	* module.c (gfc_use_module): Use gfc_warning_now_2.
	* parse.c (decode_statement): Likewise.
	(decode_gcc_attribute): Likewise.
	(next_free): Likewise.
	(next_fixed): Likewise.


gcc/testsuite/ChangeLog:

2014-11-11  Manuel López-Ibáñez  <manu@gcc.gnu.org>

	PR fortran/44054
	* lib/gfortran-dg.exp: Update regexp to match locus and message
	without caret.
	* gfortran.dg/use_without_only_1.f90: Add column numbers.
        * gfortran.dg/warnings_are_errors_1.f: Update.

From-SVN: r217383
---
 gcc/fortran/ChangeLog                         | 20 +++++++++
 gcc/fortran/error.c                           | 45 +++++++++++++++++++
 gcc/fortran/f95-lang.c                        |  4 ++
 gcc/fortran/gfortran.h                        |  4 +-
 gcc/fortran/lang.opt                          |  2 +-
 gcc/fortran/module.c                          |  5 ++-
 gcc/fortran/options.c                         |  5 ---
 gcc/fortran/parse.c                           | 18 ++++----
 gcc/testsuite/ChangeLog                       |  8 ++++
 .../gfortran.dg/use_without_only_1.f90        |  6 +--
 .../gfortran.dg/warnings_are_errors_1.f       |  3 +-
 gcc/testsuite/lib/gfortran-dg.exp             | 39 ++++++++++------
 libcpp/ChangeLog                              |  7 +++
 libcpp/include/line-map.h                     |  8 ++++
 libcpp/line-map.c                             | 44 ++++++++++++++++++
 15 files changed, 181 insertions(+), 37 deletions(-)

diff --git a/gcc/fortran/ChangeLog b/gcc/fortran/ChangeLog
index 7c89d33acda0..7fd573cd39c3 100644
--- a/gcc/fortran/ChangeLog
+++ b/gcc/fortran/ChangeLog
@@ -1,3 +1,23 @@
+2014-11-11  Manuel López-Ibáñez  <manu@gcc.gnu.org>
+
+	PR fortran/44054
+	* gfortran.h (warn_use_without_only): Remove.
+	(gfc_diagnostics_finish): Declare.
+	* error.c: Include tree-diagnostics.h
+	(gfc_format_decoder): New.
+	(gfc_diagnostics_init): Use gfc_format_decoder. Set default caret
+	char.
+	(gfc_diagnostics_finish): Restore tree diagnostics defaults, but
+	keep gfc_diagnostics_starter and finalizer. Restore default caret.
+	* options.c: Remove all uses of warn_use_without_only.
+	* lang.opt (Wuse-without-only): Add Var.
+	* f95-lang.c (gfc_be_parse_file): Call gfc_diagnostics_finish.
+	* module.c (gfc_use_module): Use gfc_warning_now_2.
+	* parse.c (decode_statement): Likewise.
+	(decode_gcc_attribute): Likewise.
+	(next_free): Likewise.
+	(next_fixed): Likewise.
+
 2014-11-11  Kyrylo Tkachov  <kyrylo.tkachov@arm.com>
 
 	PR fortran/63701
diff --git a/gcc/fortran/error.c b/gcc/fortran/error.c
index 2116f56ba472..cbab7314ac28 100644
--- a/gcc/fortran/error.c
+++ b/gcc/fortran/error.c
@@ -40,6 +40,7 @@ along with GCC; see the file COPYING3.  If not see
 
 #include "diagnostic.h"
 #include "diagnostic-color.h"
+#include "tree-diagnostic.h" /* tree_diagnostics_defaults */
 
 static int suppress_errors = 0;
 
@@ -958,6 +959,38 @@ gfc_warning_now (const char *gmsgid, ...)
   buffer_flag = i;
 }
 
+/* Called from output_format -- during diagnostic message processing
+   to handle Fortran specific format specifiers with the following meanings:
+
+   %C  Current locus (no argument)
+*/
+static bool
+gfc_format_decoder (pretty_printer *pp,
+		    text_info *text, const char *spec,
+		    int precision ATTRIBUTE_UNUSED, bool wide ATTRIBUTE_UNUSED,
+		    bool plus ATTRIBUTE_UNUSED, bool hash ATTRIBUTE_UNUSED)
+{
+  switch (*spec)
+    {
+    case 'C':
+      {
+	static const char *result = "(1)";
+	gcc_assert (gfc_current_locus.nextc - gfc_current_locus.lb->line >= 0);
+	unsigned int c1 = gfc_current_locus.nextc - gfc_current_locus.lb->line;
+	gcc_assert (text->locus);
+	*text->locus
+	  = linemap_position_for_loc_and_offset (line_table,
+						 gfc_current_locus.lb->location,
+						 c1);
+	global_dc->caret_char = '1';
+	pp_string (pp, result);
+	return true;
+      }
+    default:
+      return false;
+    }
+}
+
 /* Return a malloc'd string describing a location.  The caller is
    responsible for freeing the memory.  */
 static char *
@@ -1356,5 +1389,17 @@ gfc_diagnostics_init (void)
 {
   diagnostic_starter (global_dc) = gfc_diagnostic_starter;
   diagnostic_finalizer (global_dc) = gfc_diagnostic_finalizer;
+  diagnostic_format_decoder (global_dc) = gfc_format_decoder;
+  global_dc->caret_char = '^';
+}
+
+void
+gfc_diagnostics_finish (void)
+{
+  tree_diagnostics_defaults (global_dc);
+  /* We still want to use the gfc starter and finalizer, not the tree
+     defaults.  */
+  diagnostic_starter (global_dc) = gfc_diagnostic_starter;
+  diagnostic_finalizer (global_dc) = gfc_diagnostic_finalizer;
   global_dc->caret_char = '^';
 }
diff --git a/gcc/fortran/f95-lang.c b/gcc/fortran/f95-lang.c
index c313606733b3..223e9381e69f 100644
--- a/gcc/fortran/f95-lang.c
+++ b/gcc/fortran/f95-lang.c
@@ -230,6 +230,10 @@ gfc_be_parse_file (void)
   /* Clear the binding level stack.  */
   while (!global_bindings_p ())
     poplevel (0, 0);
+
+  /* Switch to the default tree diagnostics here, because there may be
+     diagnostics before gfc_finish().  */
+  gfc_diagnostics_finish ();
 }
 
 
diff --git a/gcc/fortran/gfortran.h b/gcc/fortran/gfortran.h
index 00bc8400e5a5..83d2b1a7d9cb 100644
--- a/gcc/fortran/gfortran.h
+++ b/gcc/fortran/gfortran.h
@@ -2455,7 +2455,6 @@ typedef struct
   int warn_tabs;
   int warn_underflow;
   int warn_intrinsic_shadow;
-  int warn_use_without_only;
   int warn_intrinsics_std;
   int warn_character_truncation;
   int warn_array_temp;
@@ -2691,7 +2690,8 @@ typedef struct gfc_error_buf
 } gfc_error_buf;
 
 void gfc_error_init_1 (void);
-void gfc_diagnostics_init(void);
+void gfc_diagnostics_init (void);
+void gfc_diagnostics_finish (void);
 void gfc_buffer_error (int);
 
 const char *gfc_print_wide_char (gfc_char_t);
diff --git a/gcc/fortran/lang.opt b/gcc/fortran/lang.opt
index b66e892e208b..d6fe60308b0b 100644
--- a/gcc/fortran/lang.opt
+++ b/gcc/fortran/lang.opt
@@ -262,7 +262,7 @@ Fortran
 ; Documented in C/C++
 
 Wuse-without-only
-Fortran Warning
+Fortran Var(warn_use_without_only) Warning
 Warn about USE statements that have no ONLY qualifier
 
 Wopenmp-simd
diff --git a/gcc/fortran/module.c b/gcc/fortran/module.c
index 1c020700ba01..56351f02c04c 100644
--- a/gcc/fortran/module.c
+++ b/gcc/fortran/module.c
@@ -6744,8 +6744,9 @@ gfc_use_module (gfc_use_list *module)
   only_flag = module->only_flag;
   current_intmod = INTMOD_NONE;
 
-  if (!only_flag && gfc_option.warn_use_without_only) 
-    gfc_warning_now ("USE statement at %C has no ONLY qualifier");
+  if (!only_flag)
+    gfc_warning_now_2 (OPT_Wuse_without_only,
+		       "USE statement at %C has no ONLY qualifier");
 
   filename = XALLOCAVEC (char, strlen (module_name) + strlen (MODULE_EXTENSION)
 			       + 1);
diff --git a/gcc/fortran/options.c b/gcc/fortran/options.c
index 8bc8f94a59d7..74b4d6d67bf7 100644
--- a/gcc/fortran/options.c
+++ b/gcc/fortran/options.c
@@ -107,7 +107,6 @@ gfc_init_options (unsigned int decoded_options_count,
   gfc_option.warn_tabs = 1;
   gfc_option.warn_underflow = 1;
   gfc_option.warn_intrinsic_shadow = 0;
-  gfc_option.warn_use_without_only = 0;
   gfc_option.warn_intrinsics_std = 0;
   gfc_option.warn_align_commons = 1;
   gfc_option.warn_real_q_constant = 0;
@@ -737,10 +736,6 @@ gfc_handle_option (size_t scode, const char *arg, int value,
       gfc_option.warn_intrinsic_shadow = value;
       break;
 
-    case OPT_Wuse_without_only:
-      gfc_option.warn_use_without_only = value;
-      break;
-
     case OPT_Walign_commons:
       gfc_option.warn_align_commons = value;
       break;
diff --git a/gcc/fortran/parse.c b/gcc/fortran/parse.c
index 4539beb19a2c..f9c16833af18 100644
--- a/gcc/fortran/parse.c
+++ b/gcc/fortran/parse.c
@@ -550,7 +550,7 @@ decode_statement (void)
      stored an error message of some sort.  */
 
   if (gfc_error_check () == 0)
-    gfc_error_now ("Unclassifiable statement at %C");
+    gfc_error_now_2 ("Unclassifiable statement at %C");
 
   reject_statement ();
 
@@ -797,7 +797,7 @@ decode_gcc_attribute (void)
      stored an error message of some sort.  */
 
   if (gfc_error_check () == 0)
-    gfc_error_now ("Unclassifiable GCC directive at %C");
+    gfc_error_now_2 ("Unclassifiable GCC directive at %C");
 
   reject_statement ();
 
@@ -836,17 +836,17 @@ next_free (void)
 	  gfc_match_small_literal_int (&i, &cnt);
 
 	  if (cnt > 5)
-	    gfc_error_now ("Too many digits in statement label at %C");
+	    gfc_error_now_2 ("Too many digits in statement label at %C");
 
 	  if (i == 0)
-	    gfc_error_now ("Zero is not a valid statement label at %C");
+	    gfc_error_now_2 ("Zero is not a valid statement label at %C");
 
 	  do
 	    c = gfc_next_ascii_char ();
 	  while (ISDIGIT(c));
 
 	  if (!gfc_is_whitespace (c))
-	    gfc_error_now ("Non-numeric character in statement label at %C");
+	    gfc_error_now_2 ("Non-numeric character in statement label at %C");
 
 	  return ST_NONE;
 	}
@@ -858,7 +858,7 @@ next_free (void)
 
 	  if (at_bol && gfc_peek_ascii_char () == ';')
 	    {
-	      gfc_error_now ("Semicolon at %C needs to be preceded by "
+	      gfc_error_now_2 ("Semicolon at %C needs to be preceded by "
 			     "statement");
 	      gfc_next_ascii_char (); /* Eat up the semicolon.  */
 	      return ST_NONE;
@@ -917,8 +917,8 @@ next_free (void)
   if (at_bol && c == ';')
     {
       if (!(gfc_option.allow_std & GFC_STD_F2008))
-	gfc_error_now ("Fortran 2008: Semicolon at %C without preceding "
-		       "statement");
+	gfc_error_now_2 ("Fortran 2008: Semicolon at %C without preceding "
+			 "statement");
       gfc_next_ascii_char (); /* Eat up the semicolon.  */
       return ST_NONE;
     }
@@ -1017,7 +1017,7 @@ next_fixed (void)
   if (digit_flag)
     {
       if (label == 0)
-	gfc_warning_now ("Zero is not a valid statement label at %C");
+	gfc_warning_now_2 ("Zero is not a valid statement label at %C");
       else
 	{
 	  /* We've found a valid statement label.  */
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 905a51ade361..9c1e65213f12 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,11 @@
+2014-11-11  Manuel López-Ibáñez  <manu@gcc.gnu.org>
+
+	PR fortran/44054
+	* lib/gfortran-dg.exp: Update regexp to match locus and message
+	without caret.
+	* gfortran.dg/use_without_only_1.f90: Add column numbers.
+        * gfortran.dg/warnings_are_errors_1.f: Update.
+
 2014-11-11  David Malcolm  <dmalcolm@redhat.com>
 
 	* ChangeLog.jit: New.
diff --git a/gcc/testsuite/gfortran.dg/use_without_only_1.f90 b/gcc/testsuite/gfortran.dg/use_without_only_1.f90
index 8554539b3eac..3fea702c2a49 100644
--- a/gcc/testsuite/gfortran.dg/use_without_only_1.f90
+++ b/gcc/testsuite/gfortran.dg/use_without_only_1.f90
@@ -6,17 +6,17 @@ MODULE foo
 END MODULE
 
 MODULE testmod
-  USE foo ! { dg-warning "has no ONLY qualifier" }
+  USE foo ! { dg-warning "6:has no ONLY qualifier" }
   IMPLICIT NONE
 CONTAINS
   SUBROUTINE S1
-     USE foo ! { dg-warning "has no ONLY qualifier" }
+     USE foo ! { dg-warning "9:has no ONLY qualifier" }
   END SUBROUTINE S1
   SUBROUTINE S2
      USE foo, ONLY: bar 
   END SUBROUTINE
   SUBROUTINE S3
-     USE ISO_C_BINDING ! { dg-warning "has no ONLY qualifier" }
+     USE ISO_C_BINDING ! { dg-warning "9:has no ONLY qualifier" }
   END SUBROUTINE S3
 END MODULE
 ! { dg-final { cleanup-modules "foo testmod" } }
diff --git a/gcc/testsuite/gfortran.dg/warnings_are_errors_1.f b/gcc/testsuite/gfortran.dg/warnings_are_errors_1.f
index 56465a9c065a..49bf1129f4ea 100644
--- a/gcc/testsuite/gfortran.dg/warnings_are_errors_1.f
+++ b/gcc/testsuite/gfortran.dg/warnings_are_errors_1.f
@@ -1,5 +1,6 @@
 ! { dg-do compile }
 ! { dg-options " -Werror" }
+! { dg-message "warnings being treated as errors" "" { target *-*-* } 0 }
 ! PR fortran/21061
 ! gfortran ignores -Werror
 ! fixed-form tests
@@ -8,7 +9,7 @@
        integer(kind=1) :: i
        real :: r1, r2(3)
 ! gfc_warning_now:
-0      r1 = 0 ! { dg-warning "Zero is not a valid statement label" }
+0      r1 = 0 ! { dg-error "Zero is not a valid statement label" }
 !
 34 5   i=0 
 ! gfc_notify_std(GFC_STD_F95_DEL):
diff --git a/gcc/testsuite/lib/gfortran-dg.exp b/gcc/testsuite/lib/gfortran-dg.exp
index 7ccaf0db0028..98958e3e6db3 100644
--- a/gcc/testsuite/lib/gfortran-dg.exp
+++ b/gcc/testsuite/lib/gfortran-dg.exp
@@ -49,34 +49,45 @@ proc gfortran-dg-test { prog do_what extra_tool_flags } {
     #              1       2
     #     Error: Some error at (1) and (2)
     #
-    # Where [locus] is either [line] or [line].[columns] .
+    # or
+    #     [name]:[locus]: Error: Some error
+    #
+    # Where [locus] is either [line] or [line].[column] or
+    # [line].[column]-[column] .
     #
     # We collapse these to look like:
     #  [name]:[line]:[column]: Error: Some error at (1) and (2)
     # or
     #  [name]:[line]:[column]: Error: Some error at (1) and (2)
     #  [name]:[line2]:[column]: Error: Some error at (1) and (2)
-    # We proceed in two steps: first we deal with the form with two
-    # different locus lines, then with the form with only one locus line.
     #
     # Note that these regexps only make sense in the combinations used below.
     # Note also that is imperative that we first deal with the form with
     # two loci.
-    set locus_regexp "(\[^\n\]*):(\[0-9\]+)\[\.:\](\[0-9\]*)(-\[0-9\]*)?:\n\n\[^\n\]*\n\[^\n\]*\n"
-    set diag_regexp "(\[^\n\]*)\n"
+    set locus_regexp "(\[^\n\]+:\[0-9\]+)\[\.:\](\[0-9\]+)(-\[0-9\]+)?:\n\n\[^\n\]+\n\[^\n\]+\n"
+    set diag_regexp "(\[^\n\]+)\n"
 
-    # Add column number if none exists
-    set colnum_regexp "(Warning: |Error: )?(\[^\n\]*):(\[0-9\]+):(\[ \n\])"
-    regsub -all $colnum_regexp $comp_output "\\2:\\3:0:\\4\\1" comp_output
+    # We proceed in steps:
 
-    set two_loci "$locus_regexp$locus_regexp$diag_regexp"
-    set single_locus "$locus_regexp$diag_regexp"
-    regsub -all $two_loci $comp_output "\\1:\\2:\\3: \\9\n\\5:\\6:\\7: \\9\n" comp_output
-    regsub -all $single_locus $comp_output "\\1:\\2:\\3: \\5\n" comp_output
+    # 1. We add first a column number if none exists.
+    # (Some Fortran diagnostics have the locus after Warning|Error)
+    set colnum_regexp "(^|\n)(Warning: |Error: )?(\[^:\n\]+:\[0-9\]+):(\[ \n\])"
+    regsub -all $colnum_regexp $comp_output "\\1\\3:0:\\4\\2" comp_output
+    verbose "comput_output0:\n$comp_output"
 
-    # Add a line number if none exists
-    regsub -all "(^|\n)(Warning: |Error: )" $comp_output "\\1:0:0: \\2" comp_output
+    # 2. We deal with the form with two different locus lines,
+    set two_loci "(^|\n)$locus_regexp$locus_regexp$diag_regexp"
+    regsub -all $two_loci $comp_output "\\1\\2:\\3: \\8\n\\5\:\\6: \\8\n" comp_output
+    verbose "comput_output1:\n$comp_output"
 
+    # 3. then with the form with only one locus line.
+    set single_locus "(^|\n)$locus_regexp$diag_regexp"
+    regsub -all $single_locus $comp_output "\\1\\2:\\3: \\5\n" comp_output
+    verbose "comput_output2:\n$comp_output"
+
+    # 4. Add a line number if none exists
+    regsub -all "(^|\n)(Warning: |Error: )" $comp_output "\\1:0:0: \\2" comp_output
+    verbose "comput_output3:\n$comp_output"
     return [list $comp_output $output_file]
 }
 
diff --git a/libcpp/ChangeLog b/libcpp/ChangeLog
index aa860b5ff1f7..b75d521cf9fb 100644
--- a/libcpp/ChangeLog
+++ b/libcpp/ChangeLog
@@ -1,3 +1,10 @@
+2014-11-11  Manuel López-Ibáñez  <manu@gcc.gnu.org>
+
+	PR fortran/44054
+	* include/line-map.h (linemap_position_for_loc_and_offset):
+	Declare.
+	* line-map.c (linemap_position_for_loc_and_offset): New.
+
 2014-11-11  David Malcolm  <dmalcolm@redhat.com>
 
 	* ChangeLog.jit: New.
diff --git a/libcpp/include/line-map.h b/libcpp/include/line-map.h
index 1f6553c94686..2fcee1906bea 100644
--- a/libcpp/include/line-map.h
+++ b/libcpp/include/line-map.h
@@ -603,6 +603,14 @@ source_location
 linemap_position_for_line_and_column (const struct line_map *,
 				      linenum_type, unsigned int);
 
+/* Encode and return a source_location starting from location LOC and
+   shifting it by OFFSET columns.  This function does not support
+   virtual locations.  */
+source_location
+linemap_position_for_loc_and_offset (struct line_maps *set,
+				     source_location loc,
+				     unsigned int offset);
+
 /* Return the file this map is for.  */
 #define LINEMAP_FILE(MAP)					\
   (linemap_check_ordinary (MAP)->d.ordinary.to_file)
diff --git a/libcpp/line-map.c b/libcpp/line-map.c
index d10d578f62e0..aff0294936c3 100644
--- a/libcpp/line-map.c
+++ b/libcpp/line-map.c
@@ -633,6 +633,50 @@ linemap_position_for_line_and_column (const struct line_map *map,
 	  + (column & ((1 << ORDINARY_MAP_NUMBER_OF_COLUMN_BITS (map)) - 1)));
 }
 
+/* Encode and return a source_location starting from location LOC and
+   shifting it by OFFSET columns.  This function does not support
+   virtual locations.  */
+
+source_location
+linemap_position_for_loc_and_offset (struct line_maps *set,
+				     source_location loc,
+				     unsigned int offset)
+{
+  const struct line_map * map = NULL;
+
+  /* This function does not support virtual locations yet.  */
+  linemap_assert (!linemap_location_from_macro_expansion_p (set, loc));
+
+  if (offset == 0
+      /* Adding an offset to a reserved location (like
+	 UNKNOWN_LOCATION for the C/C++ FEs) does not really make
+	 sense.  So let's leave the location intact in that case.  */
+      || loc < RESERVED_LOCATION_COUNT)
+    return loc;
+
+  /* We find the real location and shift it.  */
+  loc = linemap_resolve_location (set, loc, LRK_SPELLING_LOCATION, &map);
+  /* The new location (loc + offset) should be higher than the first
+     location encoded by MAP.  */
+  linemap_assert (MAP_START_LOCATION (map) < loc + offset);
+
+  /* If MAP is not the last line map of its set, then the new location
+     (loc + offset) should be less than the first location encoded by
+     the next line map of the set.  */
+  if (map != LINEMAPS_LAST_ORDINARY_MAP (set))
+    linemap_assert (loc + offset < MAP_START_LOCATION (&map[1]));
+
+  offset += SOURCE_COLUMN (map, loc);
+  linemap_assert (offset < (1u << map->d.ordinary.column_bits));
+
+  source_location r = 
+    linemap_position_for_line_and_column (map,
+					  SOURCE_LINE (map, loc),
+					  offset);
+  linemap_assert (map == linemap_lookup (set, r));
+  return r;
+}
+
 /* Given a virtual source location yielded by a map (either an
    ordinary or a macro map), returns that map.  */
 
-- 
GitLab