From 097f82ec9d19ccb5420c8df98cf35e1898b4fdab Mon Sep 17 00:00:00 2001
From: David Malcolm <dmalcolm@redhat.com>
Date: Mon, 20 Aug 2018 21:06:46 +0000
Subject: [PATCH] Add support for grouping of related diagnostics (PR
 other/84889)

We often emit logically-related groups of diagnostics.

A relatively simple case is this:

  if (warning_at (body_loc, OPT_Wmultistatement_macros,
                  "macro expands to multiple statements"))
    inform (guard_loc, "some parts of macro expansion are not guarded by "
            "this %qs clause", guard_tinfo_to_string (keyword));

where the "note" diagnostic issued by the "inform" call
is guarded by the -Wmultistatement_macros warning.

More complicated examples can be seen in the C++ frontend,
where e.g. print_z_candidates can lead to numerous "note"
diagnostics being emitted.

I'm looking at various ways to improve how we handle such related
diagnostics, but, prior to this patch, there was no explicit
relationship between these diagnostics: the diagnostics subsystem
had no way of "knowing" that these were related.

This patch introduces a simple way to group the diagnostics:
an auto_diagnostic_group class: all diagnostics emitted within
the lifetime of an auto_diagnostic_group instance are logically
grouped.

Hence in the above example, the two diagnostics can be grouped
by simply adding an auto_diagnostic_group instance:

  auto_diagnostic_group d;
  if (warning_at (body_loc, OPT_Wmultistatement_macros,
                  "macro expands to multiple statements"))
    inform (guard_loc, "some parts of macro expansion are not guarded by "
            "this %qs clause", guard_tinfo_to_string (keyword));

Some more awkard cases are of the form:

  if (some_condition
      && warning_at (...)
      && more_conditions)
    inform (...);

which thus need restructuring to:

  if (some_condition)
    {
      auto_diagnostic_group d;
      warning_at (...);
      if (more_conditions)
        inform (...);
    }

so that the lifetime of the auto_diagnostic_group groups the
warning_at and the inform call.

Nesting is handled by simply tracking a nesting depth within the
diagnostic_context.: all diagnostics are treated as grouped until the
final auto_diagnostic_group is popped.

diagnostic.c uses this internally, so that all diagnostics are part of
a group - those that are "by themselves" are treated as being part of
a group with one element.

The diagnostic_context gains optional callbacks for displaying the
start of a group (when the first diagnostic is emitted within it), and
the end of a group (for when the group was non-empty); these callbacks
are unused by default, but a test plugin demonstrates them (and verifies
that the machinery is working).

As noted above, I'm looking at various ways to use the grouping to
improve how we output the diagnostics.

FWIW, I experimented with a more involved implementation, of the form:

  diagnostic_group d;
  if (d.warning_at (body_loc, OPT_Wmultistatement_macros,
                    "macro expands to multiple statements"))
    d.inform (guard_loc, "some parts of macro expansion are not guarded by "
              "this %qs clause", guard_tinfo_to_string (keyword));

which had the advantage of allowing auto-detection of the places where
groups were needed (by converting ::warning_at's return type to bool),
but it was a much more invasive patch, especially when dealing with
the places in the C++ frontend that can emit numerous notes after
an error or warning (and thus having to pass the group around)
Hence I went with this simpler approach.

gcc/c-family/ChangeLog:
	PR other/84889
	* c-attribs.c (common_handle_aligned_attribute): Add
	auto_diagnostic_group instance.
	* c-indentation.c (warn_for_misleading_indentation): Likewise.
	* c-opts.c (c_common_post_options): Likewise.
	* c-warn.c (warn_logical_not_parentheses): Likewise.
	(warn_duplicated_cond_add_or_warn): Likewise.
	(warn_for_multistatement_macros): Likewise.

gcc/c/ChangeLog:
	PR other/84889
	* c-decl.c (pushtag): Add auto_diagnostic_group instance.
	(diagnose_mismatched_decls): Likewise, in various places.
	(warn_if_shadowing): Likewise.
	(implicit_decl_warning): Likewise.
	(implicitly_declare): Likewise.
	(undeclared_variable): Likewise.
	(declare_label): Likewise.
	(grokdeclarator): Likewise.
	(start_function): Likewise.
	* c-parser.c (c_parser_declaration_or_fndef): Likewise.
	(c_parser_parameter_declaration): Likewise.
	(c_parser_binary_expression): Likewise.
	* c-typeck.c (c_expr_sizeof_expr): Likewise.
	(parser_build_binary_op): Likewise.
	(build_unary_op): Likewise.
	(error_init): Likewise.
	(pedwarn_init): Likewise.
	(warning_init): Likewise.
	(convert_for_assignment): Likewise.

gcc/cp/ChangeLog:
	PR other/84889
	* call.c (build_user_type_conversion_1): Add auto_diagnostic_group
	instance(s).
	(print_error_for_call_failure): Likewise.
	(build_op_call_1): Likewise.
	(build_conditional_expr_1): Likewise.
	(build_new_op_1): Likewise.
	(build_op_delete_call): Likewise.
	(convert_like_real): Likewise.
	(build_over_call): Likewise.
	(build_new_method_call_1): Likewise.
	(joust): Likewise.
	* class.c (check_tag): Likewise.
	(finish_struct_anon_r): Likewise.
	(one_inherited_ctor): Likewise.
	(finalize_literal_type_property): Likewise.
	(explain_non_literal_class): Likewise.
	(find_flexarrays): Likewise.
	(resolve_address_of_overloaded_function): Likewise.
	* constexpr.c (ensure_literal_type_for_constexpr_object): Likewise.
	(is_valid_constexpr_fn): Likewise.
	(cx_check_missing_mem_inits): Likewise.
	* cp-gimplify.c (cp_genericize_r): Likewise.
	* cvt.c (maybe_warn_nodiscard): Likewise.
	* decl.c (warn_extern_redeclared_static): Likewise.
	(check_redeclaration_exception_specification): Likewise.
	(check_no_redeclaration_friend_default_args): Likewise.
	(duplicate_decls): Likewise.
	(redeclaration_error_message): Likewise.
	(warn_misplaced_attr_for_class_type): Likewise.
	* decl2.c (finish_static_data_member_decl): Likewise.
	(no_linkage_error): Likewise.
	(cp_warn_deprecated_use): Likewise.
	* error.c (qualified_name_lookup_error): Likewise.
	* friend.c (make_friend_class): Likewise.
	(do_friend): Likewise.
	* init.c (perform_member_init): Likewise.
	(build_new_1): Likewise.
	(build_vec_delete_1): Likewise.
	(build_delete): Likewise.
	* lex.c (unqualified_name_lookup_error): Likewise.
	* name-lookup.c (check_extern_c_conflict): Likewise.
	(inform_shadowed): New function.
	(check_local_shadow): Add auto_diagnostic_group instances,
	replacing goto "inform_shadowed" label with call to subroutine.
	(set_local_extern_decl_linkage): Add auto_diagnostic_group
	instance(s).
	* parser.c (cp_parser_diagnose_invalid_type_name): Likewise.
	(cp_parser_namespace_name): Likewise.
	* pt.c (check_specialization_namespace): Likewise.
	(check_template_variable): Likewise.
	(warn_spec_missing_attributes): Likewise.
	(check_explicit_specialization): Likewise.
	(process_partial_specialization): Likewise.
	(lookup_template_class_1): Likewise.
	(finish_template_variable): Likewise.
	(do_auto_deduction): Likewise.
	* search.c (check_final_overrider): Likewise.
	(look_for_overrides_r): Likewise.
	* tree.c (maybe_warn_parm_abi): Likewise.
	* typeck.c (cxx_sizeof_expr): Likewise.
	(cp_build_function_call_vec): Likewise.
	(cp_build_binary_op): Likewise.
	(convert_for_assignment): Likewise.
	(maybe_warn_about_returning_address_of_local): Likewise.
	* typeck2.c (abstract_virtuals_error_sfinae): Likewise.
	(check_narrowing): Likewise.

gcc/ChangeLog:
	PR other/84889
	* attribs.c (diag_attr_exclusions): Add auto_diagnostic_group instance.
	(decl_attributes): Likewise.
	* calls.c (maybe_warn_nonstring_arg): Add auto_diagnostic_group
	instance.
	* cgraphunit.c (maybe_diag_incompatible_alias): Likewise.
	* diagnostic-core.h (class auto_diagnostic_group): New class.
	* diagnostic.c (diagnostic_initialize): Initialize the new fields.
	(diagnostic_report_diagnostic): Handle the first diagnostics within
	a group.
	(emit_diagnostic): Add auto_diagnostic_group instance.
	(inform): Likewise.
	(inform_n): Likewise.
	(warning): Likewise.
	(warning_at): Likewise.
	(warning_n): Likewise.
	(pedwarn): Likewise.
	(permerror): Likewise.
	(error): Likewise.
	(error_n): Likewise.
	(error_at): Likewise.
	(sorry): Likewise.
	(fatal_error): Likewise.
	(internal_error): Likewise.
	(internal_error_no_backtrace): Likewise.
	(auto_diagnostic_group::auto_diagnostic_group): New ctor.
	(auto_diagnostic_group::~auto_diagnostic_group): New dtor.
	* diagnostic.h (struct diagnostic_context): Add fields
	"diagnostic_group_nesting_depth",
	"diagnostic_group_emission_count", "begin_group_cb",
	"end_group_cb".
	* gimple-ssa-isolate-paths.c (find_implicit_erroneous_behavior):
	Add auto_diagnostic_group instance(s).
	(find_explicit_erroneous_behavior): Likewise.
	* gimple-ssa-warn-alloca.c (pass_walloca::execute): Likewise.
	* gimple-ssa-warn-restrict.c (maybe_diag_offset_bounds): Likewise.
	* gimplify.c (warn_implicit_fallthrough_r): Likewise.
	(gimplify_va_arg_expr): Likewise.
	* hsa-gen.c (HSA_SORRY_ATV): Likewise.
	(HSA_SORRY_AT): Likewise.
	* ipa-devirt.c (compare_virtual_tables): Likewise.
	(warn_odr): Likewise.
	* multiple_target.c (expand_target_clones): Likewise.
	* opts-common.c (cmdline_handle_error): Likewise.
	* reginfo.c (globalize_reg): Likewise.
	* substring-locations.c (format_warning_n_va): Likewise.
	* tree-inline.c (expand_call_inline): Likewise.
	* tree-ssa-ccp.c (pass_post_ipa_warn::execute): Likewise.
	* tree-ssa-loop-niter.c
	(do_warn_aggressive_loop_optimizations): Likewise.
	* tree-ssa-uninit.c (warn_uninit): Likewise.
	* tree.c (warn_deprecated_use): Likewise.

gcc/testsuite/ChangeLog:
	PR other/84889
	* gcc.dg/plugin/diagnostic-group-test-1.c: New test.
	* gcc.dg/plugin/diagnostic_group_plugin.c: New test.
	* gcc.dg/plugin/plugin.exp (plugin_test_list): Add the new tests.

From-SVN: r263675
---
 gcc/ChangeLog                                 |  55 ++++
 gcc/attribs.c                                 |   3 +-
 gcc/c-family/ChangeLog                        |  11 +
 gcc/c-family/c-attribs.c                      |   1 +
 gcc/c-family/c-indentation.c                  |   1 +
 gcc/c-family/c-opts.c                         |   1 +
 gcc/c-family/c-warn.c                         |   3 +
 gcc/c/ChangeLog                               |  23 ++
 gcc/c/c-decl.c                                |  44 +++-
 gcc/c/c-parser.c                              |  22 +-
 gcc/c/c-typeck.c                              |  78 ++++--
 gcc/calls.c                                   |   1 +
 gcc/cgraphunit.c                              |  17 +-
 gcc/cp/ChangeLog                              |  70 ++++++
 gcc/cp/call.c                                 |  29 ++-
 gcc/cp/class.c                                |  75 +++---
 gcc/cp/constexpr.c                            |  21 +-
 gcc/cp/cp-gimplify.c                          |  15 +-
 gcc/cp/cvt.c                                  |   3 +
 gcc/cp/decl.c                                 |  28 ++-
 gcc/cp/decl2.c                                |   3 +
 gcc/cp/error.c                                |   2 +
 gcc/cp/friend.c                               |   4 +
 gcc/cp/init.c                                 |  48 ++--
 gcc/cp/lex.c                                  |   1 +
 gcc/cp/name-lookup.c                          |  35 +--
 gcc/cp/parser.c                               |   6 +
 gcc/cp/pt.c                                   |   8 +
 gcc/cp/search.c                               |  10 +
 gcc/cp/tree.c                                 |   2 +
 gcc/cp/typeck.c                               |  49 ++--
 gcc/cp/typeck2.c                              |   2 +
 gcc/diagnostic-core.h                         |   9 +
 gcc/diagnostic.c                              |  60 +++++
 gcc/diagnostic.h                              |  17 ++
 gcc/gimple-ssa-isolate-paths.c                |  26 +-
 gcc/gimple-ssa-warn-alloca.c                  |  50 ++--
 gcc/gimple-ssa-warn-restrict.c                |   2 +
 gcc/gimplify.c                                |   2 +
 gcc/hsa-gen.c                                 |   2 +
 gcc/ipa-devirt.c                              |  39 +--
 gcc/multiple_target.c                         |   1 +
 gcc/opts-common.c                             |   1 +
 gcc/reginfo.c                                 |   1 +
 gcc/substring-locations.c                     |   1 +
 gcc/testsuite/ChangeLog                       |   7 +
 .../gcc.dg/plugin/diagnostic-group-test-1.c   |  26 ++
 .../gcc.dg/plugin/diagnostic_group_plugin.c   | 234 ++++++++++++++++++
 gcc/testsuite/gcc.dg/plugin/plugin.exp        |   2 +
 gcc/tree-inline.c                             |   1 +
 gcc/tree-ssa-ccp.c                            |   1 +
 gcc/tree-ssa-loop-niter.c                     |   1 +
 gcc/tree-ssa-uninit.c                         |   1 +
 gcc/tree.c                                    |   2 +
 54 files changed, 963 insertions(+), 194 deletions(-)
 create mode 100644 gcc/testsuite/gcc.dg/plugin/diagnostic-group-test-1.c
 create mode 100644 gcc/testsuite/gcc.dg/plugin/diagnostic_group_plugin.c

diff --git a/gcc/ChangeLog b/gcc/ChangeLog
index eb7ac76f675b..515ea8a087a2 100644
--- a/gcc/ChangeLog
+++ b/gcc/ChangeLog
@@ -1,3 +1,58 @@
+2018-08-20  David Malcolm  <dmalcolm@redhat.com>
+
+	PR other/84889
+	* attribs.c (diag_attr_exclusions): Add auto_diagnostic_group instance.
+	(decl_attributes): Likewise.
+	* calls.c (maybe_warn_nonstring_arg): Add auto_diagnostic_group
+	instance.
+	* cgraphunit.c (maybe_diag_incompatible_alias): Likewise.
+	* diagnostic-core.h (class auto_diagnostic_group): New class.
+	* diagnostic.c (diagnostic_initialize): Initialize the new fields.
+	(diagnostic_report_diagnostic): Handle the first diagnostics within
+	a group.
+	(emit_diagnostic): Add auto_diagnostic_group instance.
+	(inform): Likewise.
+	(inform_n): Likewise.
+	(warning): Likewise.
+	(warning_at): Likewise.
+	(warning_n): Likewise.
+	(pedwarn): Likewise.
+	(permerror): Likewise.
+	(error): Likewise.
+	(error_n): Likewise.
+	(error_at): Likewise.
+	(sorry): Likewise.
+	(fatal_error): Likewise.
+	(internal_error): Likewise.
+	(internal_error_no_backtrace): Likewise.
+	(auto_diagnostic_group::auto_diagnostic_group): New ctor.
+	(auto_diagnostic_group::~auto_diagnostic_group): New dtor.
+	* diagnostic.h (struct diagnostic_context): Add fields
+	"diagnostic_group_nesting_depth",
+	"diagnostic_group_emission_count", "begin_group_cb",
+	"end_group_cb".
+	* gimple-ssa-isolate-paths.c (find_implicit_erroneous_behavior):
+	Add auto_diagnostic_group instance(s).
+	(find_explicit_erroneous_behavior): Likewise.
+	* gimple-ssa-warn-alloca.c (pass_walloca::execute): Likewise.
+	* gimple-ssa-warn-restrict.c (maybe_diag_offset_bounds): Likewise.
+	* gimplify.c (warn_implicit_fallthrough_r): Likewise.
+	(gimplify_va_arg_expr): Likewise.
+	* hsa-gen.c (HSA_SORRY_ATV): Likewise.
+	(HSA_SORRY_AT): Likewise.
+	* ipa-devirt.c (compare_virtual_tables): Likewise.
+	(warn_odr): Likewise.
+	* multiple_target.c (expand_target_clones): Likewise.
+	* opts-common.c (cmdline_handle_error): Likewise.
+	* reginfo.c (globalize_reg): Likewise.
+	* substring-locations.c (format_warning_n_va): Likewise.
+	* tree-inline.c (expand_call_inline): Likewise.
+	* tree-ssa-ccp.c (pass_post_ipa_warn::execute): Likewise.
+	* tree-ssa-loop-niter.c
+	(do_warn_aggressive_loop_optimizations): Likewise.
+	* tree-ssa-uninit.c (warn_uninit): Likewise.
+	* tree.c (warn_deprecated_use): Likewise.
+
 2018-08-20  H.J. Lu  <hongjiu.lu@intel.com>
 
 	PR target/87014
diff --git a/gcc/attribs.c b/gcc/attribs.c
index efc879ba4767..64700b6c8ce3 100644
--- a/gcc/attribs.c
+++ b/gcc/attribs.c
@@ -430,7 +430,7 @@ diag_attr_exclusions (tree last_decl, tree node, tree attrname,
 
 	  /* Print a note?  */
 	  bool note = last_decl != NULL_TREE;
-
+	  auto_diagnostic_group d;
 	  if (TREE_CODE (node) == FUNCTION_DECL
 	      && DECL_BUILT_IN (node))
 	    note &= warning (OPT_Wattributes,
@@ -587,6 +587,7 @@ decl_attributes (tree *node, tree attributes, int flags,
 	  /* This is a c++11 attribute that appertains to a
 	     type-specifier, outside of the definition of, a class
 	     type.  Ignore it.  */
+	  auto_diagnostic_group d;
 	  if (warning (OPT_Wattributes, "attribute ignored"))
 	    inform (input_location,
 		    "an attribute that appertains to a type-specifier "
diff --git a/gcc/c-family/ChangeLog b/gcc/c-family/ChangeLog
index 9ff4728fd67b..aa52815cc751 100644
--- a/gcc/c-family/ChangeLog
+++ b/gcc/c-family/ChangeLog
@@ -1,3 +1,14 @@
+2018-08-20  David Malcolm  <dmalcolm@redhat.com>
+
+	PR other/84889
+	* c-attribs.c (common_handle_aligned_attribute): Add
+	auto_diagnostic_group instance.
+	* c-indentation.c (warn_for_misleading_indentation): Likewise.
+	* c-opts.c (c_common_post_options): Likewise.
+	* c-warn.c (warn_logical_not_parentheses): Likewise.
+	(warn_duplicated_cond_add_or_warn): Likewise.
+	(warn_for_multistatement_macros): Likewise.
+
 2018-08-20  Nathan Sidwell  <nathan@acm.org>
 
 	* c-ada-spec.c (macro_length, dump_ada_macros): Adjust macro parm
diff --git a/gcc/c-family/c-attribs.c b/gcc/c-family/c-attribs.c
index 9da9c2765e34..5454e09adbcb 100644
--- a/gcc/c-family/c-attribs.c
+++ b/gcc/c-family/c-attribs.c
@@ -1881,6 +1881,7 @@ common_handle_aligned_attribute (tree *node, tree name, tree args, int flags,
       bitalign /= BITS_PER_UNIT;
 
       bool diagd = true;
+      auto_diagnostic_group d;
       if (DECL_USER_ALIGN (decl) || DECL_USER_ALIGN (last_decl))
 	diagd = warning (OPT_Wattributes,
 			  "ignoring attribute %<%E (%u)%> because it conflicts "
diff --git a/gcc/c-family/c-indentation.c b/gcc/c-family/c-indentation.c
index 436d61b3c9af..cff5aec23c23 100644
--- a/gcc/c-family/c-indentation.c
+++ b/gcc/c-family/c-indentation.c
@@ -609,6 +609,7 @@ warn_for_misleading_indentation (const token_indent_info &guard_tinfo,
 					      body_tinfo,
 					      next_tinfo))
     {
+      auto_diagnostic_group d;
       if (warning_at (guard_tinfo.location, OPT_Wmisleading_indentation,
 		      "this %qs clause does not guard...",
 		      guard_tinfo_to_string (guard_tinfo.keyword)))
diff --git a/gcc/c-family/c-opts.c b/gcc/c-family/c-opts.c
index cb69fb3513c7..ec0577139d09 100644
--- a/gcc/c-family/c-opts.c
+++ b/gcc/c-family/c-opts.c
@@ -931,6 +931,7 @@ c_common_post_options (const char **pfilename)
       warn_abi_version = latest_abi_version;
       if (flag_abi_version == latest_abi_version)
 	{
+	  auto_diagnostic_group d;
 	  if (warning (OPT_Wabi, "-Wabi won't warn about anything"))
 	    {
 	      inform (input_location, "-Wabi warns about differences "
diff --git a/gcc/c-family/c-warn.c b/gcc/c-family/c-warn.c
index d34d6672937c..ca259aa7bd0c 100644
--- a/gcc/c-family/c-warn.c
+++ b/gcc/c-family/c-warn.c
@@ -491,6 +491,7 @@ warn_logical_not_parentheses (location_t location, enum tree_code code,
       && integer_zerop (rhs))
     return;
 
+  auto_diagnostic_group d;
   if (warning_at (location, OPT_Wlogical_not_parentheses,
 		  "logical not is only applied to the left hand side of "
 		  "comparison")
@@ -2232,6 +2233,7 @@ warn_duplicated_cond_add_or_warn (location_t loc, tree cond, vec<tree> **chain)
   FOR_EACH_VEC_ELT (**chain, ix, t)
     if (operand_equal_p (cond, t, 0))
       {
+	auto_diagnostic_group d;
 	if (warning_at (loc, OPT_Wduplicated_cond,
 			"duplicated %<if%> condition"))
 	  inform (EXPR_LOCATION (t), "previously used here");
@@ -2601,6 +2603,7 @@ warn_for_multistatement_macros (location_t body_loc, location_t next_loc,
 	return;
     }
 
+  auto_diagnostic_group d;
   if (warning_at (body_loc, OPT_Wmultistatement_macros,
 		  "macro expands to multiple statements"))
     inform (guard_loc, "some parts of macro expansion are not guarded by "
diff --git a/gcc/c/ChangeLog b/gcc/c/ChangeLog
index 7bde11c1f195..e943f0aac4a9 100644
--- a/gcc/c/ChangeLog
+++ b/gcc/c/ChangeLog
@@ -1,3 +1,26 @@
+2018-08-20  David Malcolm  <dmalcolm@redhat.com>
+
+	PR other/84889
+	* c-decl.c (pushtag): Add auto_diagnostic_group instance.
+	(diagnose_mismatched_decls): Likewise, in various places.
+	(warn_if_shadowing): Likewise.
+	(implicit_decl_warning): Likewise.
+	(implicitly_declare): Likewise.
+	(undeclared_variable): Likewise.
+	(declare_label): Likewise.
+	(grokdeclarator): Likewise.
+	(start_function): Likewise.
+	* c-parser.c (c_parser_declaration_or_fndef): Likewise.
+	(c_parser_parameter_declaration): Likewise.
+	(c_parser_binary_expression): Likewise.
+	* c-typeck.c (c_expr_sizeof_expr): Likewise.
+	(parser_build_binary_op): Likewise.
+	(build_unary_op): Likewise.
+	(error_init): Likewise.
+	(pedwarn_init): Likewise.
+	(warning_init): Likewise.
+	(convert_for_assignment): Likewise.
+
 2018-08-15  David Malcolm  <dmalcolm@redhat.com>
 
 	* c-objc-common.c: Include "gcc-rich-location.h".
diff --git a/gcc/c/c-decl.c b/gcc/c/c-decl.c
index 1bbccddab31d..95249779e3c8 100644
--- a/gcc/c/c-decl.c
+++ b/gcc/c/c-decl.c
@@ -1571,6 +1571,7 @@ pushtag (location_t loc, tree name, tree type)
 	  && (TYPE_MAIN_VARIANT (TREE_TYPE (b->decl))
 	      != TYPE_MAIN_VARIANT (type)))
 	{
+	  auto_diagnostic_group d;
 	  if (warning_at (loc, OPT_Wc___compat,
 			  ("using %qD as both a typedef and a tag is "
 			   "invalid in C++"), b->decl)
@@ -1823,8 +1824,6 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 			   tree *newtypep, tree *oldtypep)
 {
   tree newtype, oldtype;
-  bool pedwarned = false;
-  bool warned = false;
   bool retval = true;
 
 #define DECL_EXTERN_INLINE(DECL) (DECL_DECLARED_INLINE_P (DECL)  \
@@ -1847,6 +1846,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	    && DECL_BUILT_IN (olddecl)
 	    && !C_DECL_DECLARED_BUILTIN (olddecl)))
 	{
+	  auto_diagnostic_group d;
 	  error ("%q+D redeclared as different kind of symbol", newdecl);
 	  locate_old_decl (olddecl);
 	}
@@ -1864,11 +1864,16 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
      given scope.  */
   if (TREE_CODE (olddecl) == CONST_DECL)
     {
+      auto_diagnostic_group d;
       error ("redeclaration of enumerator %q+D", newdecl);
       locate_old_decl (olddecl);
       return false;
     }
 
+  bool pedwarned = false;
+  bool warned = false;
+  auto_diagnostic_group d;
+
   if (!comptypes (oldtype, newtype))
     {
       if (TREE_CODE (olddecl) == FUNCTION_DECL
@@ -2052,6 +2057,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 		  )
 		  && same_translation_unit_p (newdecl, olddecl))
 		{
+		  auto_diagnostic_group d;
 		  error ("redefinition of %q+D", newdecl);
 		  locate_old_decl (olddecl);
 		  return false;
@@ -2062,11 +2068,14 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	 the argument types must be checked specially.  */
       else if (DECL_INITIAL (olddecl)
 	       && !prototype_p (oldtype) && prototype_p (newtype)
-	       && TYPE_ACTUAL_ARG_TYPES (oldtype)
-	       && !validate_proto_after_old_defn (newdecl, newtype, oldtype))
+	       && TYPE_ACTUAL_ARG_TYPES (oldtype))
 	{
-	  locate_old_decl (olddecl);
-	  return false;
+	  auto_diagnostic_group d;
+	  if (!validate_proto_after_old_defn (newdecl, newtype, oldtype))
+	    {
+	      locate_old_decl (olddecl);
+	      return false;
+	    }
 	}
       /* A non-static declaration (even an "extern") followed by a
 	 static declaration is undefined behavior per C99 6.2.2p3-5,7.
@@ -2087,6 +2096,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	  if (!DECL_IS_BUILTIN (olddecl)
 	      && !DECL_EXTERN_INLINE (olddecl))
 	    {
+	      auto_diagnostic_group d;
 	      error ("static declaration of %q+D follows "
 		     "non-static declaration", newdecl);
 	      locate_old_decl (olddecl);
@@ -2097,6 +2107,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	{
 	  if (DECL_CONTEXT (olddecl))
 	    {
+	      auto_diagnostic_group d;
 	      error ("non-static declaration of %q+D follows "
 		     "static declaration", newdecl);
 	      locate_old_decl (olddecl);
@@ -2121,6 +2132,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 					DECL_ATTRIBUTES (olddecl)) != NULL;
 	  if (newa != olda)
 	    {
+	      auto_diagnostic_group d;
 	      error_at (input_location, "%<gnu_inline%> attribute present on %q+D",
 			newa ? newdecl : olddecl);
 	      error_at (DECL_SOURCE_LOCATION (newa ? olddecl : newdecl),
@@ -2141,6 +2153,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	}
       else if (DECL_THREAD_LOCAL_P (newdecl) != DECL_THREAD_LOCAL_P (olddecl))
 	{
+	  auto_diagnostic_group d;
 	  if (DECL_THREAD_LOCAL_P (newdecl))
 	    error ("thread-local declaration of %q+D follows "
 		   "non-thread-local declaration", newdecl);
@@ -2155,6 +2168,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
       /* Multiple initialized definitions are not allowed (6.9p3,5).  */
       if (DECL_INITIAL (newdecl) && DECL_INITIAL (olddecl))
 	{
+	  auto_diagnostic_group d;
 	  error ("redefinition of %q+D", newdecl);
 	  locate_old_decl (olddecl);
 	  return false;
@@ -2175,6 +2189,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	    {
 	      if (!DECL_FILE_SCOPE_P (olddecl))
 		{
+		  auto_diagnostic_group d;
 		  error ("extern declaration of %q+D follows "
 			 "declaration with no linkage", newdecl);
 		  locate_old_decl (olddecl);
@@ -2189,6 +2204,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	    }
 	  else
 	    {
+	      auto_diagnostic_group d;
 	      if (TREE_PUBLIC (newdecl))
 		error ("non-static declaration of %q+D follows "
 		       "static declaration", newdecl);
@@ -2211,12 +2227,14 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
 	    }
 	  else if (DECL_EXTERNAL (olddecl))
 	    {
+	      auto_diagnostic_group d;
 	      error ("declaration of %q+D with no linkage follows "
 		     "extern declaration", newdecl);
 	      locate_old_decl (olddecl);
 	    }
 	  else
 	    {
+	      auto_diagnostic_group d;
 	      error ("redeclaration of %q+D with no linkage", newdecl);
 	      locate_old_decl (olddecl);
 	    }
@@ -2263,6 +2281,7 @@ diagnose_mismatched_decls (tree newdecl, tree olddecl,
       if (TREE_CODE (newdecl) == PARM_DECL
 	  && (!TREE_ASM_WRITTEN (olddecl) || TREE_ASM_WRITTEN (newdecl)))
 	{
+	  auto_diagnostic_group d;
 	  error ("redefinition of parameter %q+D", newdecl);
 	  locate_old_decl (olddecl);
 	  return false;
@@ -2778,7 +2797,6 @@ warn_if_shadowing (tree new_decl)
 					     DECL_SOURCE_LOCATION (b->decl))))
       {
 	tree old_decl = b->decl;
-	bool warned = false;
 
 	if (old_decl == error_mark_node)
 	  {
@@ -2786,7 +2804,10 @@ warn_if_shadowing (tree new_decl)
 		     "non-variable", new_decl);
 	    break;
 	  }
-	else if (TREE_CODE (old_decl) == PARM_DECL)
+
+	bool warned = false;
+	auto_diagnostic_group d;
+	if (TREE_CODE (old_decl) == PARM_DECL)
 	  {
 	    enum opt_code warning_code;
 
@@ -3123,6 +3144,7 @@ implicit_decl_warning (location_t loc, tree id, tree olddecl)
     return;
 
   bool warned;
+  auto_diagnostic_group d;
   name_hint hint;
   if (!olddecl)
     hint = lookup_name_fuzzy (id, FUZZY_LOOKUP_FUNCTION_NAME, loc);
@@ -3435,6 +3457,7 @@ implicitly_declare (location_t loc, tree functionid)
 	    {
 	      if (!comptypes (newtype, TREE_TYPE (decl)))
 		{
+		  auto_diagnostic_group d;
 		  error_at (loc, "incompatible implicit declaration of "
 			    "function %qD", decl);
 		  locate_old_decl (decl);
@@ -3487,6 +3510,7 @@ undeclared_variable (location_t loc, tree id)
   static bool already = false;
   struct c_scope *scope;
 
+  auto_diagnostic_group d;
   if (current_function_decl == NULL_TREE)
     {
       name_hint guessed_id = lookup_name_fuzzy (id, FUZZY_LOOKUP_NAME, loc);
@@ -3686,6 +3710,7 @@ declare_label (tree name)
      at this scope */
   if (b && B_IN_CURRENT_SCOPE (b))
     {
+      auto_diagnostic_group d;
       error ("duplicate label declaration %qE", name);
       locate_old_decl (b->decl);
 
@@ -3784,6 +3809,7 @@ define_label (location_t location, tree name)
 	  || (DECL_CONTEXT (label) != current_function_decl
 	      && C_DECLARED_LABEL_FLAG (label))))
     {
+      auto_diagnostic_group d;
       error_at (location, "duplicate label %qD", label);
       locate_old_decl (label);
       return NULL_TREE;
@@ -6720,6 +6746,7 @@ grokdeclarator (const struct c_declarator *declarator,
 		  || (current_scope == file_scope && B_IN_EXTERNAL_SCOPE (b)))
 	      && TYPE_MAIN_VARIANT (b->decl) != TYPE_MAIN_VARIANT (type))
 	    {
+	      auto_diagnostic_group d;
 	      if (warning_at (declarator->id_loc, OPT_Wc___compat,
 			      ("using %qD as both a typedef and a tag is "
 			       "invalid in C++"), decl)
@@ -8794,6 +8821,7 @@ start_function (struct c_declspecs *declspecs, struct c_declarator *declarator,
 	{
 	  if (stdarg_p (TREE_TYPE (old_decl)))
 	    {
+	      auto_diagnostic_group d;
 	      warning_at (loc, 0, "%q+D defined as variadic function "
 			  "without prototype", decl1);
 	      locate_old_decl (old_decl);
diff --git a/gcc/c/c-parser.c b/gcc/c/c-parser.c
index 5ad4f57a4fe7..0d5dbea8f677 100644
--- a/gcc/c/c-parser.c
+++ b/gcc/c/c-parser.c
@@ -1814,6 +1814,7 @@ c_parser_declaration_or_fndef (c_parser *parser, bool fndef_ok,
 	}
       else
 	{
+	  auto_diagnostic_group d;
 	  name_hint hint = lookup_name_fuzzy (name, FUZZY_LOOKUP_TYPENAME,
 					      here);
 	  if (hint)
@@ -4058,6 +4059,7 @@ c_parser_parameter_declaration (c_parser *parser, tree attrs)
       c_parser_set_source_position_from_token (token);
       if (c_parser_next_tokens_start_typename (parser, cla_prefer_type))
 	{
+	  auto_diagnostic_group d;
 	  name_hint hint = lookup_name_fuzzy (token->value,
 					      FUZZY_LOOKUP_TYPENAME,
 					      token->location);
@@ -6873,14 +6875,18 @@ c_parser_binary_expression (c_parser *parser, struct c_expr *after,
 		&& !(TREE_CODE (first_arg) == PARM_DECL			      \
 		     && C_ARRAY_PARAMETER (first_arg)			      \
 		     && warn_sizeof_array_argument))			      \
-	      if (warning_at (stack[sp].loc, OPT_Wsizeof_pointer_div,	      \
-			      "division %<sizeof (%T) / sizeof (%T)%> does "  \
-			      "not compute the number of array elements",     \
-			      type0, type1))				      \
-		if (DECL_P (first_arg))					      \
-		  inform (DECL_SOURCE_LOCATION (first_arg),		      \
-			  "first %<sizeof%> operand was declared here");      \
-	  }								      \
+	      {								\
+		auto_diagnostic_group d;					\
+		if (warning_at (stack[sp].loc, OPT_Wsizeof_pointer_div, \
+				  "division %<sizeof (%T) / sizeof (%T)%> " \
+				  "does not compute the number of array " \
+				  "elements",				\
+				  type0, type1))			\
+		  if (DECL_P (first_arg))				\
+		    inform (DECL_SOURCE_LOCATION (first_arg),		\
+			      "first %<sizeof%> operand was declared here"); \
+	      }								\
+	  }								\
 	break;								      \
       default:								      \
 	break;								      \
diff --git a/gcc/c/c-typeck.c b/gcc/c/c-typeck.c
index 726ea832ae10..54c7967a06b8 100644
--- a/gcc/c/c-typeck.c
+++ b/gcc/c/c-typeck.c
@@ -2906,6 +2906,7 @@ c_expr_sizeof_expr (location_t loc, struct c_expr expr)
       if (TREE_CODE (expr.value) == PARM_DECL
 	  && C_ARRAY_PARAMETER (expr.value))
 	{
+	  auto_diagnostic_group d;
 	  if (warning_at (loc, OPT_Wsizeof_array_argument,
 			  "%<sizeof%> on array function parameter %qE will "
 			  "return size of %qT", expr.value,
@@ -3735,19 +3736,27 @@ parser_build_binary_op (location_t location, enum tree_code code,
 		    "comparison with string literal results in unspecified behavior");
       /* Warn for ptr == '\0', it's likely that it should've been ptr[0].  */
       if (POINTER_TYPE_P (type1)
-	   && null_pointer_constant_p (arg2.value)
-	   && char_type_p (type2)
-	   && warning_at (location, OPT_Wpointer_compare,
-			  "comparison between pointer and zero character "
-			  "constant"))
-	inform (arg1.get_start (), "did you mean to dereference the pointer?");
+	  && null_pointer_constant_p (arg2.value)
+	  && char_type_p (type2))
+	{
+	  auto_diagnostic_group d;
+	  if (warning_at (location, OPT_Wpointer_compare,
+			    "comparison between pointer and zero character "
+			    "constant"))
+	    inform (arg1.get_start (),
+		      "did you mean to dereference the pointer?");
+	}
       else if (POINTER_TYPE_P (type2)
 	       && null_pointer_constant_p (arg1.value)
-	       && char_type_p (type1)
-	       && warning_at (location, OPT_Wpointer_compare,
-			      "comparison between pointer and zero character "
-			      "constant"))
-	inform (arg2.get_start (), "did you mean to dereference the pointer?");
+	       && char_type_p (type1))
+	{
+	  auto_diagnostic_group d;
+	  if (warning_at (location, OPT_Wpointer_compare,
+			    "comparison between pointer and zero character "
+			    "constant"))
+	    inform (arg2.get_start (),
+		      "did you mean to dereference the pointer?");
+	}
     }
   else if (TREE_CODE_CLASS (code) == tcc_comparison
 	   && (code1 == STRING_CST || code2 == STRING_CST))
@@ -4288,13 +4297,16 @@ build_unary_op (location_t location, enum tree_code code, tree xarg,
 	    e = TREE_OPERAND (e, 1);
 
 	  if ((TREE_CODE (TREE_TYPE (arg)) == BOOLEAN_TYPE
-	       || truth_value_p (TREE_CODE (e)))
-	      && warning_at (location, OPT_Wbool_operation,
-			     "%<~%> on a boolean expression"))
+	       || truth_value_p (TREE_CODE (e))))
 	    {
-	      gcc_rich_location richloc (location);
-	      richloc.add_fixit_insert_before (location, "!");
-	      inform (&richloc, "did you mean to use logical not?");
+	      auto_diagnostic_group d;
+	      if (warning_at (location, OPT_Wbool_operation,
+				"%<~%> on a boolean expression"))
+		{
+		  gcc_rich_location richloc (location);
+		  richloc.add_fixit_insert_before (location, "!");
+		  inform (&richloc, "did you mean to use logical not?");
+		}
 	    }
 	  if (!noconvert)
 	    arg = default_conversion (arg);
@@ -6197,6 +6209,8 @@ error_init (location_t loc, const char *gmsgid)
 {
   char *ofwhat;
 
+  auto_diagnostic_group d;
+
   /* The gmsgid may be a format string with %< and %>. */
   error_at (loc, gmsgid);
   ofwhat = print_spelling ((char *) alloca (spelling_length () + 1));
@@ -6216,7 +6230,7 @@ pedwarn_init (location_t loc, int opt, const char *gmsgid, ...)
      it was defined to make sure macros defined in system headers
      but used incorrectly elsewhere are diagnosed.  */
   source_location exploc = expansion_point_location_if_in_system_header (loc);
-
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   bool warned = emit_diagnostic_valist (DK_PEDWARN, exploc, opt, gmsgid, &ap);
@@ -6238,6 +6252,8 @@ warning_init (location_t loc, int opt, const char *gmsgid)
   char *ofwhat;
   bool warned;
 
+  auto_diagnostic_group d;
+
   /* Use the location where a macro was expanded rather than where
      it was defined to make sure macros defined in system headers
      but used incorrectly elsewhere are diagnosed.  */
@@ -6379,8 +6395,11 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
     switch (errtype)                                                     \
       {                                                                  \
       case ic_argpass:                                                   \
-        if (pedwarn (PLOC, OPT, AR, parmnum, rname))			 \
-          inform_for_arg (fundecl, (PLOC), parmnum, type, rhstype);	\
+	{								\
+	  auto_diagnostic_group d;						\
+	  if (pedwarn (PLOC, OPT, AR, parmnum, rname))		\
+	    inform_for_arg (fundecl, (PLOC), parmnum, type, rhstype); \
+	}								\
         break;                                                           \
       case ic_assign:                                                    \
         pedwarn (LOCATION, OPT, AS);                                     \
@@ -6405,8 +6424,11 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
     switch (errtype)                                                     \
       {                                                                  \
       case ic_argpass:                                                   \
-        if (pedwarn (PLOC, OPT, AR, parmnum, rname, QUALS))		 \
-          inform_for_arg (fundecl, (PLOC), parmnum, type, rhstype);	\
+	{								\
+	auto_diagnostic_group d;						\
+	if (pedwarn (PLOC, OPT, AR, parmnum, rname, QUALS))		\
+	  inform_for_arg (fundecl, (PLOC), parmnum, type, rhstype);	\
+	}								\
         break;                                                           \
       case ic_assign:                                                    \
         pedwarn (LOCATION, OPT, AS, QUALS);				 \
@@ -6431,8 +6453,11 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
     switch (errtype)                                                     \
       {                                                                  \
       case ic_argpass:                                                   \
-        if (warning_at (PLOC, OPT, AR, parmnum, rname, QUALS))           \
-          inform_for_arg (fundecl, (PLOC), parmnum, type, rhstype);      \
+	{								\
+	  auto_diagnostic_group d;						\
+	  if (warning_at (PLOC, OPT, AR, parmnum, rname, QUALS))	\
+	    inform_for_arg (fundecl, (PLOC), parmnum, type, rhstype); \
+	}								\
         break;                                                           \
       case ic_assign:                                                    \
         warning_at (LOCATION, OPT, AS, QUALS);                           \
@@ -6925,6 +6950,7 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 		  {
 		  case ic_argpass:
 		    {
+		      auto_diagnostic_group d;
 		      range_label_for_type_mismatch rhs_label (rhstype, type);
 		      gcc_rich_location richloc (expr_loc, &rhs_label);
 		      if (pedwarn (&richloc, OPT_Wpointer_sign,
@@ -6984,6 +7010,7 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 	    {
 	    case ic_argpass:
 	      {
+		auto_diagnostic_group d;
 		range_label_for_type_mismatch rhs_label (rhstype, type);
 		gcc_rich_location richloc (expr_loc, &rhs_label);
 		if (pedwarn (&richloc, OPT_Wincompatible_pointer_types,
@@ -7031,6 +7058,7 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 	  {
 	  case ic_argpass:
 	    {
+	      auto_diagnostic_group d;
 	      range_label_for_type_mismatch rhs_label (rhstype, type);
 	      gcc_rich_location richloc (expr_loc, &rhs_label);
 	      if (pedwarn (&richloc, OPT_Wint_conversion,
@@ -7066,6 +7094,7 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
 	{
 	case ic_argpass:
 	  {
+	    auto_diagnostic_group d;
 	    range_label_for_type_mismatch rhs_label (rhstype, type);
 	    gcc_rich_location richloc (expr_loc, &rhs_label);
 	    if (pedwarn (&richloc, OPT_Wint_conversion,
@@ -7109,6 +7138,7 @@ convert_for_assignment (location_t location, location_t expr_loc, tree type,
     {
     case ic_argpass:
       {
+	auto_diagnostic_group d;
 	range_label_for_type_mismatch rhs_label (rhstype, type);
 	gcc_rich_location richloc (expr_loc, &rhs_label);
 	error_at (&richloc, "incompatible type for argument %d of %qE", parmnum,
diff --git a/gcc/calls.c b/gcc/calls.c
index 384c0238748d..0fb10b182b1a 100644
--- a/gcc/calls.c
+++ b/gcc/calls.c
@@ -1773,6 +1773,7 @@ maybe_warn_nonstring_arg (tree fndecl, tree exp)
 
       bool warned = false;
 
+      auto_diagnostic_group d;
       if (wi::ltu_p (asize, wibnd))
 	{
 	  if (bndrng[0] == bndrng[1])
diff --git a/gcc/cgraphunit.c b/gcc/cgraphunit.c
index 462e247328ea..208798f0dc7a 100644
--- a/gcc/cgraphunit.c
+++ b/gcc/cgraphunit.c
@@ -1358,6 +1358,7 @@ maybe_diag_incompatible_alias (tree alias, tree target)
 	{
 	  funcptr = build_pointer_type (funcptr);
 
+	  auto_diagnostic_group d;
 	  if (warning_at (DECL_SOURCE_LOCATION (target),
 			  OPT_Wattribute_alias,
 			  "%<ifunc%> resolver for %qD should return %qT",
@@ -1365,12 +1366,16 @@ maybe_diag_incompatible_alias (tree alias, tree target)
 	    inform (DECL_SOURCE_LOCATION (alias),
 		    "resolver indirect function declared here");
 	}
-      else if (warning_at (DECL_SOURCE_LOCATION (alias),
-			   OPT_Wattribute_alias,
-			   "%qD alias between functions of incompatible "
-			   "types %qT and %qT", alias, altype, targtype))
-	inform (DECL_SOURCE_LOCATION (target),
-		"aliased declaration here");
+      else
+	{
+	  auto_diagnostic_group d;
+	  if (warning_at (DECL_SOURCE_LOCATION (alias),
+			    OPT_Wattribute_alias,
+			    "%qD alias between functions of incompatible "
+			    "types %qT and %qT", alias, altype, targtype))
+	    inform (DECL_SOURCE_LOCATION (target),
+		      "aliased declaration here");
+	}
     }
 }
 
diff --git a/gcc/cp/ChangeLog b/gcc/cp/ChangeLog
index d8be93089b4c..28c09740aa69 100644
--- a/gcc/cp/ChangeLog
+++ b/gcc/cp/ChangeLog
@@ -1,3 +1,73 @@
+2018-08-20  David Malcolm  <dmalcolm@redhat.com>
+
+	PR other/84889
+	* call.c (build_user_type_conversion_1): Add auto_diagnostic_group
+	instance(s).
+	(print_error_for_call_failure): Likewise.
+	(build_op_call_1): Likewise.
+	(build_conditional_expr_1): Likewise.
+	(build_new_op_1): Likewise.
+	(build_op_delete_call): Likewise.
+	(convert_like_real): Likewise.
+	(build_over_call): Likewise.
+	(build_new_method_call_1): Likewise.
+	(joust): Likewise.
+	* class.c (check_tag): Likewise.
+	(finish_struct_anon_r): Likewise.
+	(one_inherited_ctor): Likewise.
+	(finalize_literal_type_property): Likewise.
+	(explain_non_literal_class): Likewise.
+	(find_flexarrays): Likewise.
+	(resolve_address_of_overloaded_function): Likewise.
+	* constexpr.c (ensure_literal_type_for_constexpr_object): Likewise.
+	(is_valid_constexpr_fn): Likewise.
+	(cx_check_missing_mem_inits): Likewise.
+	* cp-gimplify.c (cp_genericize_r): Likewise.
+	* cvt.c (maybe_warn_nodiscard): Likewise.
+	* decl.c (warn_extern_redeclared_static): Likewise.
+	(check_redeclaration_exception_specification): Likewise.
+	(check_no_redeclaration_friend_default_args): Likewise.
+	(duplicate_decls): Likewise.
+	(redeclaration_error_message): Likewise.
+	(warn_misplaced_attr_for_class_type): Likewise.
+	* decl2.c (finish_static_data_member_decl): Likewise.
+	(no_linkage_error): Likewise.
+	(cp_warn_deprecated_use): Likewise.
+	* error.c (qualified_name_lookup_error): Likewise.
+	* friend.c (make_friend_class): Likewise.
+	(do_friend): Likewise.
+	* init.c (perform_member_init): Likewise.
+	(build_new_1): Likewise.
+	(build_vec_delete_1): Likewise.
+	(build_delete): Likewise.
+	* lex.c (unqualified_name_lookup_error): Likewise.
+	* name-lookup.c (check_extern_c_conflict): Likewise.
+	(inform_shadowed): New function.
+	(check_local_shadow): Add auto_diagnostic_group instances,
+	replacing goto "inform_shadowed" label with call to subroutine.
+	(set_local_extern_decl_linkage): Add auto_diagnostic_group
+	instance(s).
+	* parser.c (cp_parser_diagnose_invalid_type_name): Likewise.
+	(cp_parser_namespace_name): Likewise.
+	* pt.c (check_specialization_namespace): Likewise.
+	(check_template_variable): Likewise.
+	(warn_spec_missing_attributes): Likewise.
+	(check_explicit_specialization): Likewise.
+	(process_partial_specialization): Likewise.
+	(lookup_template_class_1): Likewise.
+	(finish_template_variable): Likewise.
+	(do_auto_deduction): Likewise.
+	* search.c (check_final_overrider): Likewise.
+	(look_for_overrides_r): Likewise.
+	* tree.c (maybe_warn_parm_abi): Likewise.
+	* typeck.c (cxx_sizeof_expr): Likewise.
+	(cp_build_function_call_vec): Likewise.
+	(cp_build_binary_op): Likewise.
+	(convert_for_assignment): Likewise.
+	(maybe_warn_about_returning_address_of_local): Likewise.
+	* typeck2.c (abstract_virtuals_error_sfinae): Likewise.
+	(check_narrowing): Likewise.
+
 2018-08-17  David Malcolm  <dmalcolm@redhat.com>
 
 	* typeck.c (string_conv_p): Extract location from EXP and use it
diff --git a/gcc/cp/call.c b/gcc/cp/call.c
index 16bb6bfd4672..1f72ac863bde 100644
--- a/gcc/cp/call.c
+++ b/gcc/cp/call.c
@@ -3968,6 +3968,7 @@ build_user_type_conversion_1 (tree totype, tree expr, int flags,
     {
       if (complain & tf_error)
 	{
+	  auto_diagnostic_group d;
 	  error ("conversion from %qH to %qI is ambiguous",
 		 fromtype, totype);
 	  print_z_candidates (location_of (expr), candidates);
@@ -4280,6 +4281,7 @@ print_error_for_call_failure (tree fn, vec<tree, va_gc> *args,
   if (targs)
     name = lookup_template_function (name, targs);
 
+  auto_diagnostic_group d;
   if (!any_strictly_viable (candidates))
     error_at (loc, "no matching function for call to %<%D(%A)%>",
 	      name, build_tree_list_vec (args));
@@ -4590,6 +4592,7 @@ build_op_call_1 (tree obj, vec<tree, va_gc> **args, tsubst_flags_t complain)
     {
       if (complain & tf_error)
         {
+          auto_diagnostic_group d;
           error ("no match for call to %<(%T) (%A)%>", TREE_TYPE (obj),
 		 build_tree_list_vec (*args));
           print_z_candidates (location_of (TREE_TYPE (obj)), candidates);
@@ -4603,6 +4606,7 @@ build_op_call_1 (tree obj, vec<tree, va_gc> **args, tsubst_flags_t complain)
 	{
           if (complain & tf_error)
             {
+              auto_diagnostic_group d;
               error ("call of %<(%T) (%A)%> is ambiguous", 
                      TREE_TYPE (obj), build_tree_list_vec (*args));
               print_z_candidates (location_of (TREE_TYPE (obj)), candidates);
@@ -5229,6 +5233,7 @@ build_conditional_expr_1 (location_t loc, tree arg1, tree arg2, tree arg3,
 	{
           if (complain & tf_error)
             {
+              auto_diagnostic_group d;
               op_error (loc, COND_EXPR, NOP_EXPR, arg1, arg2, arg3, FALSE);
               print_z_candidates (loc, candidates);
             }
@@ -5860,6 +5865,7 @@ build_new_op_1 (location_t loc, enum tree_code code, int flags, tree arg1,
 		  {
 		    /* ... Otherwise, report the more generic
 		       "no matching operator found" error */
+		    auto_diagnostic_group d;
 		    op_error (loc, code, code2, arg1, arg2, arg3, FALSE);
 		    print_z_candidates (loc, candidates);
 		  }
@@ -5875,6 +5881,7 @@ build_new_op_1 (location_t loc, enum tree_code code, int flags, tree arg1,
 	{
 	  if (complain & tf_error)
 	    {
+	      auto_diagnostic_group d;
 	      op_error (loc, code, code2, arg1, arg2, arg3, TRUE);
 	      print_z_candidates (loc, candidates);
 	    }
@@ -6311,14 +6318,18 @@ build_op_delete_call (enum tree_code code, tree addr, tree size,
 	     -Wc++14-compat.  */
 	  else if (!flag_sized_deallocation)
 	    {
-	      if ((complain & tf_warning)
-		  && warning (OPT_Wc__14_compat, msg1))
-		inform (DECL_SOURCE_LOCATION (fn), msg2, fn);
+	      if (complain & tf_warning)
+		{
+		  auto_diagnostic_group d;
+		  if (warning (OPT_Wc__14_compat, msg1))
+		    inform (DECL_SOURCE_LOCATION (fn), msg2, fn);
+		}
 	      goto ok;
 	    }
 
 	  if (complain & tf_warning_or_error)
 	    {
+	      auto_diagnostic_group d;
 	      if (permerror (input_location, msg1))
 		{
 		  /* Only mention C++14 for namespace-scope delete.  */
@@ -6712,6 +6723,7 @@ convert_like_real (conversion *convs, tree expr, tree fn, int argnum,
 	{
 	  if (t->kind == ck_user && t->cand->reason)
 	    {
+	      auto_diagnostic_group d;
 	      complained = permerror (loc, "invalid user-defined conversion "
 				      "from %qH to %qI", TREE_TYPE (expr),
 				      totype);
@@ -6795,6 +6807,7 @@ convert_like_real (conversion *convs, tree expr, tree fn, int argnum,
 	    if (CONSTRUCTOR_NELTS (expr) == 0
 		&& FUNCTION_FIRST_USER_PARMTYPE (convfn) != void_list_node)
 	      {
+		auto_diagnostic_group d;
 		if (pedwarn (loc, 0, "converting to %qT from initializer list "
 			     "would use explicit constructor %qD",
 			     totype, convfn))
@@ -6973,6 +6986,7 @@ convert_like_real (conversion *convs, tree expr, tree fn, int argnum,
 	{
 	  if (complain & tf_error)
 	    {
+	      auto_diagnostic_group d;
 	      maybe_print_user_conv_context (convs);
 	      if (fn)
 		inform (DECL_SOURCE_LOCATION (fn),
@@ -7025,6 +7039,7 @@ convert_like_real (conversion *convs, tree expr, tree fn, int argnum,
       expr = build_temp (expr, totype, flags, &diag_kind, complain);
       if (diag_kind && complain)
 	{
+	  auto_diagnostic_group d;
 	  maybe_print_user_conv_context (convs);
 	  if (fn)
 	    inform (DECL_SOURCE_LOCATION (fn),
@@ -7040,6 +7055,7 @@ convert_like_real (conversion *convs, tree expr, tree fn, int argnum,
 	if (convs->bad_p && !next_conversion (convs)->bad_p)
 	  {
 	    tree extype = TREE_TYPE (expr);
+	    auto_diagnostic_group d;
 	    if (TYPE_REF_IS_RVALUE (ref_type)
 		&& lvalue_p (expr))
 	      error_at (loc, "cannot bind rvalue reference of type %qH to "
@@ -7931,6 +7947,7 @@ build_over_call (struct z_candidate *cand, int flags, tsubst_flags_t complain)
 	{
 	  if (complain & tf_error)
 	    {
+	      auto_diagnostic_group d;
 	      if (permerror (input_location, "passing %qT as %<this%> "
 			     "argument discards qualifiers",
 			     TREE_TYPE (argtype)))
@@ -9212,6 +9229,7 @@ build_new_method_call_1 (tree instance, tree fns, vec<tree, va_gc> **args,
 
       basetype = DECL_CONTEXT (fn);
       name = constructor_name (basetype);
+      auto_diagnostic_group d;
       if (permerror (input_location,
 		     "cannot call constructor %<%T::%D%> directly",
 		     basetype, name))
@@ -9350,6 +9368,7 @@ build_new_method_call_1 (tree instance, tree fns, vec<tree, va_gc> **args,
     {
       if (complain & tf_error)
 	{
+	  auto_diagnostic_group d;
 	  if (!COMPLETE_OR_OPEN_TYPE_P (basetype))
 	    cxx_incomplete_type_error (instance, basetype);
 	  else if (optype)
@@ -9393,6 +9412,7 @@ build_new_method_call_1 (tree instance, tree fns, vec<tree, va_gc> **args,
 	      arglist = build_tree_list_vec (user_args);
 	      if (skip_first_for_error)
 		arglist = TREE_CHAIN (arglist);
+	      auto_diagnostic_group d;
 	      if (!any_strictly_viable (candidates))
 		error ("no matching function for call to %<%s(%A)%>",
 		       pretty_name, arglist);
@@ -10299,6 +10319,7 @@ joust (struct z_candidate *cand1, struct z_candidate *cand2, bool warn,
 	  tree source = source_type (w->convs[0]);
 	  if (INDIRECT_TYPE_P (source))
 	    source = TREE_TYPE (source);
+	  auto_diagnostic_group d;
 	  if (warning (OPT_Wconversion, "choosing %qD over %qD", w->fn, l->fn)
 	      && warning (OPT_Wconversion, "  for conversion from %qH to %qI",
 			  source, w->second_conv->type)) 
@@ -10526,6 +10547,7 @@ joust (struct z_candidate *cand1, struct z_candidate *cand2, bool warn,
 		{
 		  if (complain & tf_error)
 		    {
+		      auto_diagnostic_group d;
 		      if (permerror (input_location,
 				     "default argument mismatch in "
 				     "overload resolution"))
@@ -10577,6 +10599,7 @@ tweak:
 	    return 0;
 	  if (warn)
 	    {
+	      auto_diagnostic_group d;
 	      pedwarn (input_location, 0,
 	      "ISO C++ says that these are ambiguous, even "
 	      "though the worst conversion for the first is better than "
diff --git a/gcc/cp/class.c b/gcc/cp/class.c
index 7b10b20ede5e..e11173d2e59b 100644
--- a/gcc/cp/class.c
+++ b/gcc/cp/class.c
@@ -1331,6 +1331,7 @@ check_tag (tree tag, tree id, tree *tp, abi_tag_data *p)
       /* Otherwise we're diagnosing missing tags.  */
       if (TREE_CODE (p->t) == FUNCTION_DECL)
 	{
+	  auto_diagnostic_group d;
 	  if (warning (OPT_Wabi_tag, "%qD inherits the %E ABI tag "
 		       "that %qT (used in its return type) has",
 		       p->t, tag, *tp))
@@ -1338,12 +1339,14 @@ check_tag (tree tag, tree id, tree *tp, abi_tag_data *p)
 	}
       else if (VAR_P (p->t))
 	{
+	  auto_diagnostic_group d;
 	  if (warning (OPT_Wabi_tag, "%qD inherits the %E ABI tag "
 		       "that %qT (used in its type) has", p->t, tag, *tp))
 	    inform (location_of (*tp), "%qT declared here", *tp);
 	}
       else if (TYPE_P (p->subob))
 	{
+	  auto_diagnostic_group d;
 	  if (warning (OPT_Wabi_tag, "%qT does not have the %E ABI tag "
 		       "that base %qT has", p->t, tag, p->subob))
 	    inform (location_of (p->subob), "%qT declared here",
@@ -1351,6 +1354,7 @@ check_tag (tree tag, tree id, tree *tp, abi_tag_data *p)
 	}
       else
 	{
+	  auto_diagnostic_group d;
 	  if (warning (OPT_Wabi_tag, "%qT does not have the %E ABI tag "
 		       "that %qT (used in the type of %qD) has",
 		       p->t, tag, *tp, p->subob))
@@ -2904,20 +2908,24 @@ finish_struct_anon_r (tree field, bool complain)
 	{
 	  /* We already complained about static data members in
 	     finish_static_data_member_decl.  */
-	  if (!VAR_P (elt)
-	      && permerror (DECL_SOURCE_LOCATION (elt),
-			    TREE_CODE (TREE_TYPE (field)) == UNION_TYPE
-			    ? "%q#D invalid; an anonymous union may "
-			    "only have public non-static data members"
-			    : "%q#D invalid; an anonymous struct may "
-			    "only have public non-static data members", elt))
+	  if (!VAR_P (elt))
 	    {
-	      static bool hint;
-	      if (flag_permissive && !hint)
+	      auto_diagnostic_group d;
+	      if (permerror (DECL_SOURCE_LOCATION (elt),
+			     TREE_CODE (TREE_TYPE (field)) == UNION_TYPE
+			     ? "%q#D invalid; an anonymous union may "
+			     "only have public non-static data members"
+			     : "%q#D invalid; an anonymous struct may "
+			     "only have public non-static data members", elt))
 		{
-		  hint = true;
-		  inform (DECL_SOURCE_LOCATION (elt),
-			  "this flexibility is deprecated and will be removed");
+		  static bool hint;
+		  if (flag_permissive && !hint)
+		    {
+		      hint = true;
+		      inform (DECL_SOURCE_LOCATION (elt),
+			      "this flexibility is deprecated and will be "
+			      "removed");
+		    }
 		}
 	    }
 	}
@@ -3107,6 +3115,7 @@ one_inherited_ctor (tree ctor, tree t, tree using_decl)
   one_inheriting_sig (t, ctor, new_parms, i);
   if (parms == NULL_TREE)
     {
+      auto_diagnostic_group d;
       if (warning (OPT_Winherited_variadic_ctor,
 		   "the ellipsis in %qD is not inherited", ctor))
 	inform (DECL_SOURCE_LOCATION (ctor), "%qD declared here", ctor);
@@ -5399,11 +5408,14 @@ finalize_literal_type_property (tree t)
 	  && !DECL_CONSTRUCTOR_P (fn))
 	{
 	  DECL_DECLARED_CONSTEXPR_P (fn) = false;
-	  if (!DECL_GENERATED_P (fn)
-	      && pedwarn (DECL_SOURCE_LOCATION (fn), OPT_Wpedantic,
-			  "enclosing class of %<constexpr%> non-static member "
-			  "function %q+#D is not a literal type", fn))
-	    explain_non_literal_class (t);
+	  if (!DECL_GENERATED_P (fn))
+	    {
+	      auto_diagnostic_group d;
+	      if (pedwarn (DECL_SOURCE_LOCATION (fn), OPT_Wpedantic,
+			     "enclosing class of %<constexpr%> non-static "
+			     "member function %q+#D is not a literal type", fn))
+		explain_non_literal_class (t);
+	    }
 	}
 }
 
@@ -5425,6 +5437,7 @@ explain_non_literal_class (tree t)
     /* Already explained.  */
     return;
 
+  auto_diagnostic_group d;
   inform (UNKNOWN_LOCATION, "%q+T is not literal because:", t);
   if (cxx_dialect < cxx17 && LAMBDA_TYPE_P (t))
     inform (UNKNOWN_LOCATION,
@@ -6626,17 +6639,20 @@ find_flexarrays (tree t, flexmems_t *fmem, bool base_p,
 static void
 diagnose_invalid_flexarray (const flexmems_t *fmem)
 {
-  if (fmem->array && fmem->enclosing
-      && pedwarn (location_of (fmem->enclosing), OPT_Wpedantic,
-		  TYPE_DOMAIN (TREE_TYPE (fmem->array))
-		  ? G_("invalid use of %q#T with a zero-size array "
-		       "in %q#D")
-		  : G_("invalid use of %q#T with a flexible array member "
-		       "in %q#T"),
-		  DECL_CONTEXT (fmem->array),
-		  DECL_CONTEXT (fmem->enclosing)))
-    inform (DECL_SOURCE_LOCATION (fmem->array),
-	    "array member %q#D declared here", fmem->array);
+  if (fmem->array && fmem->enclosing)
+    {
+      auto_diagnostic_group d;
+      if (pedwarn (location_of (fmem->enclosing), OPT_Wpedantic,
+		     TYPE_DOMAIN (TREE_TYPE (fmem->array))
+		     ? G_("invalid use of %q#T with a zero-size array "
+			  "in %q#D")
+		     : G_("invalid use of %q#T with a flexible array member "
+			  "in %q#T"),
+		     DECL_CONTEXT (fmem->array),
+		     DECL_CONTEXT (fmem->enclosing)))
+	inform (DECL_SOURCE_LOCATION (fmem->array),
+		  "array member %q#D declared here", fmem->array);
+    }
 }
 
 /* Issue diagnostics for invalid flexible array members or zero-length
@@ -6671,6 +6687,7 @@ diagnose_flexarrays (tree t, const flexmems_t *fmem)
 	{
 	  location_t loc = DECL_SOURCE_LOCATION (fmem->array);
 
+	  auto_diagnostic_group d;
 	  if (pedwarn (loc, OPT_Wpedantic, msg, fmem->array, t))
 	    {
 	      inform (location_of (t), "in the definition of %q#T", t);
@@ -6690,6 +6707,7 @@ diagnose_flexarrays (tree t, const flexmems_t *fmem)
 	  location_t loc = DECL_SOURCE_LOCATION (fmem->array);
 	  diagd = true;
 
+	  auto_diagnostic_group d;
 	  error_at (loc, msg, fmem->array, t);
 
 	  /* In the unlikely event that the member following the flexible
@@ -7923,6 +7941,7 @@ resolve_address_of_overloaded_function (tree target_type,
       if (!(complain & tf_error))
 	return error_mark_node;
 
+      auto_diagnostic_group d;
       if (permerror (input_location, "assuming pointer to member %qD", fn)
 	  && !explained)
 	{
diff --git a/gcc/cp/constexpr.c b/gcc/cp/constexpr.c
index ece2c8a92d99..54c8b5edf8d1 100644
--- a/gcc/cp/constexpr.c
+++ b/gcc/cp/constexpr.c
@@ -97,6 +97,7 @@ ensure_literal_type_for_constexpr_object (tree decl)
 	{
 	  if (DECL_DECLARED_CONSTEXPR_P (decl))
 	    {
+	      auto_diagnostic_group d;
 	      error ("the type %qT of %<constexpr%> variable %qD "
 		     "is not literal", type, decl);
 	      explain_non_literal_class (type);
@@ -106,6 +107,7 @@ ensure_literal_type_for_constexpr_object (tree decl)
 	    {
 	      if (!is_instantiation_of_constexpr (current_function_decl))
 		{
+		  auto_diagnostic_group d;
 		  error ("variable %qD of non-literal type %qT in %<constexpr%> "
 			 "function", decl, type);
 		  explain_non_literal_class (type);
@@ -200,6 +202,7 @@ is_valid_constexpr_fn (tree fun, bool complain)
 	    ret = false;
 	    if (complain)
 	      {
+		auto_diagnostic_group d;
 		error ("invalid type for parameter %d of %<constexpr%> "
 		       "function %q+#D", DECL_PARM_INDEX (parm), fun);
 		explain_non_literal_class (TREE_TYPE (parm));
@@ -222,6 +225,7 @@ is_valid_constexpr_fn (tree fun, bool complain)
 	  ret = false;
 	  if (complain)
 	    {
+	      auto_diagnostic_group d;
 	      error ("invalid return type %qT of %<constexpr%> function %q+D",
 		     rettype, fun);
 	      explain_non_literal_class (rettype);
@@ -234,11 +238,15 @@ is_valid_constexpr_fn (tree fun, bool complain)
 	  && !CLASSTYPE_LITERAL_P (DECL_CONTEXT (fun)))
 	{
 	  ret = false;
-	  if (complain
-	      && pedwarn (DECL_SOURCE_LOCATION (fun), OPT_Wpedantic,
-			  "enclosing class of %<constexpr%> non-static member "
-			  "function %q+#D is not a literal type", fun))
-	    explain_non_literal_class (DECL_CONTEXT (fun));
+	  if (complain)
+	    {
+	      auto_diagnostic_group d;
+	      if (pedwarn (DECL_SOURCE_LOCATION (fun), OPT_Wpedantic,
+			     "enclosing class of %<constexpr%> non-static"
+			     " member function %q+#D is not a literal type",
+			     fun))
+		explain_non_literal_class (DECL_CONTEXT (fun));
+	    }
 	}
     }
   else if (CLASSTYPE_VBASECLASSES (DECL_CONTEXT (fun)))
@@ -818,6 +826,7 @@ cx_check_missing_mem_inits (tree ctype, tree body, bool complain)
 	    }
 	  if (!complain)
 	    return true;
+	  auto_diagnostic_group d;
 	  error ("member %qD must be initialized by mem-initializer "
 		 "in %<constexpr%> constructor", field);
 	  inform (DECL_SOURCE_LOCATION (field), "declared here");
@@ -4303,6 +4312,7 @@ cxx_eval_constant_expression (const constexpr_ctx *ctx, tree t,
 	{
 	  if (!ctx->quiet)
 	    {
+	      auto_diagnostic_group d;
 	      error ("temporary of non-literal type %qT in a "
 		     "constant expression", TREE_TYPE (t));
 	      explain_non_literal_class (TREE_TYPE (t));
@@ -5995,6 +6005,7 @@ potential_constant_expression_1 (tree t, bool want_rval, bool strict, bool now,
 	{
 	  if (flags & tf_error)
 	    {
+	      auto_diagnostic_group d;
 	      error_at (loc, "temporary of non-literal type %qT in a "
 			"constant expression", TREE_TYPE (t));
 	      explain_non_literal_class (TREE_TYPE (t));
diff --git a/gcc/cp/cp-gimplify.c b/gcc/cp/cp-gimplify.c
index 7db4accb5043..f61099141026 100644
--- a/gcc/cp/cp-gimplify.c
+++ b/gcc/cp/cp-gimplify.c
@@ -1420,12 +1420,15 @@ cp_genericize_r (tree *stmt_p, int *walk_subtrees, void *data)
 	  /* Never mind.  */;
 	else if (wtd->try_block)
 	  {
-	    if (TREE_CODE (wtd->try_block) == MUST_NOT_THROW_EXPR
-		&& warning_at (loc, OPT_Wterminate,
-			       "throw will always call terminate()")
-		&& cxx_dialect >= cxx11
-		&& DECL_DESTRUCTOR_P (current_function_decl))
-	      inform (loc, "in C++11 destructors default to noexcept");
+	    if (TREE_CODE (wtd->try_block) == MUST_NOT_THROW_EXPR)
+	      {
+		auto_diagnostic_group d;
+		if (warning_at (loc, OPT_Wterminate,
+				"throw will always call terminate()")
+		    && cxx_dialect >= cxx11
+		    && DECL_DESTRUCTOR_P (current_function_decl))
+		  inform (loc, "in C++11 destructors default to noexcept");
+	      }
 	  }
 	else
 	  {
diff --git a/gcc/cp/cvt.c b/gcc/cp/cvt.c
index da9841485562..315b0d6a65ac 100644
--- a/gcc/cp/cvt.c
+++ b/gcc/cp/cvt.c
@@ -1017,6 +1017,7 @@ maybe_warn_nodiscard (tree expr, impl_conv_void implicit)
   if (implicit != ICV_CAST && fn
       && lookup_attribute ("nodiscard", DECL_ATTRIBUTES (fn)))
     {
+      auto_diagnostic_group d;
       if (warning_at (loc, OPT_Wunused_result,
 		      "ignoring return value of %qD, "
 		      "declared with attribute nodiscard", fn))
@@ -1025,6 +1026,7 @@ maybe_warn_nodiscard (tree expr, impl_conv_void implicit)
   else if (implicit != ICV_CAST
 	   && lookup_attribute ("nodiscard", TYPE_ATTRIBUTES (rettype)))
     {
+      auto_diagnostic_group d;
       if (warning_at (loc, OPT_Wunused_result,
 		      "ignoring returned value of type %qT, "
 		      "declared with attribute nodiscard", rettype))
@@ -1043,6 +1045,7 @@ maybe_warn_nodiscard (tree expr, impl_conv_void implicit)
 	 result is used, so handle that case here.  */
       if (fn)
 	{
+	  auto_diagnostic_group d;
 	  if (warning_at (loc, OPT_Wunused_result,
 			  "ignoring return value of %qD, "
 			  "declared with attribute warn_unused_result",
diff --git a/gcc/cp/decl.c b/gcc/cp/decl.c
index fa58bc4d2b3e..f6dbd6b11c36 100644
--- a/gcc/cp/decl.c
+++ b/gcc/cp/decl.c
@@ -1133,6 +1133,7 @@ warn_extern_redeclared_static (tree newdecl, tree olddecl)
       && DECL_ARTIFICIAL (olddecl))
     return;
 
+  auto_diagnostic_group d;
   if (permerror (DECL_SOURCE_LOCATION (newdecl),
 		 "%qD was declared %<extern%> and later %<static%>", newdecl))
     inform (DECL_SOURCE_LOCATION (olddecl),
@@ -1176,6 +1177,7 @@ check_redeclaration_exception_specification (tree new_decl,
 	= G_("declaration of %qF has a different exception specifier");
       bool complained = true;
       location_t new_loc = DECL_SOURCE_LOCATION (new_decl);
+      auto_diagnostic_group d;
       if (DECL_IN_SYSTEM_HEADER (old_decl))
 	complained = pedwarn (new_loc, OPT_Wsystem_headers, msg, new_decl);
       else if (!flag_exceptions)
@@ -1304,6 +1306,7 @@ check_no_redeclaration_friend_default_args (tree olddecl, tree newdecl,
     if ((olddecl_hidden_friend_p && TREE_PURPOSE (t1))
 	|| (DECL_FRIEND_P (newdecl) && TREE_PURPOSE (t2)))
       {
+	auto_diagnostic_group d;
 	if (permerror (DECL_SOURCE_LOCATION (newdecl),
 		       "friend declaration of %q#D specifies default "
 		       "arguments and isn't the only declaration", newdecl))
@@ -1555,6 +1558,7 @@ next_arg:;
 				    "declaration %q#D", newdecl, olddecl);
 			  return error_mark_node;
 			}
+		      auto_diagnostic_group d;
 		      if (permerror (newdecl_loc,
 				     "new declaration %q#D ambiguates built-in"
 				     " declaration %q#D", newdecl, olddecl)
@@ -1801,6 +1805,7 @@ next_arg:;
       const char *errmsg = redeclaration_error_message (newdecl, olddecl);
       if (errmsg)
 	{
+	  auto_diagnostic_group d;
 	  error_at (newdecl_loc, errmsg, newdecl);
 	  if (DECL_NAME (olddecl) != NULL_TREE)
 	    inform (olddecl_loc,
@@ -1815,6 +1820,7 @@ next_arg:;
 	       && prototype_p (TREE_TYPE (newdecl)))
 	{
 	  /* Prototype decl follows defn w/o prototype.  */
+	  auto_diagnostic_group d;
 	  if (warning_at (newdecl_loc, 0,
 			  "prototype specified for %q#D", newdecl))
 	    inform (olddecl_loc,
@@ -1856,6 +1862,7 @@ next_arg:;
 	    }
 	  else
 	    {
+	      auto_diagnostic_group d;
 	      error_at (newdecl_loc,
 			"conflicting declaration of %q#D with %qL linkage",
 			newdecl, DECL_LANGUAGE (newdecl));
@@ -1893,6 +1900,7 @@ next_arg:;
 		    if (simple_cst_equal (TREE_PURPOSE (t1),
 					  TREE_PURPOSE (t2)) == 1)
 		      {
+			auto_diagnostic_group d;
 			if (permerror (newdecl_loc,
 				       "default argument given for parameter "
 				       "%d of %q#D", i, newdecl))
@@ -1902,6 +1910,7 @@ next_arg:;
 		      }
 		    else
 		      {
+			auto_diagnostic_group d;
 			error_at (newdecl_loc,
 				  "default argument given for parameter %d "
 				  "of %q#D", i, newdecl);
@@ -1977,6 +1986,7 @@ next_arg:;
 	  && (! DECL_TEMPLATE_SPECIALIZATION (newdecl)
 	      || DECL_TEMPLATE_SPECIALIZATION (olddecl)))
 	{
+	  auto_diagnostic_group d;
 	  if (warning_at (newdecl_loc,
 			  OPT_Wredundant_decls,
 			  "redundant redeclaration of %qD in same scope",
@@ -1990,6 +2000,7 @@ next_arg:;
 	{
 	  if (DECL_DELETED_FN (newdecl))
 	    {
+	      auto_diagnostic_group d;
 	      error_at (newdecl_loc, "deleted definition of %qD", newdecl);
 	      inform (olddecl_loc,
 		      "previous declaration of %qD", olddecl);
@@ -2567,6 +2578,7 @@ next_arg:;
       && DECL_VISIBILITY_SPECIFIED (newdecl)
       && DECL_VISIBILITY (newdecl) != DECL_VISIBILITY (olddecl))
     {
+      auto_diagnostic_group d;
       if (warning_at (newdecl_loc, OPT_Wattributes,
 		      "%qD: visibility attribute ignored because it "
 		      "conflicts with previous declaration", newdecl))
@@ -2986,12 +2998,15 @@ redeclaration_error_message (tree newdecl, tree olddecl)
 	{
 	  DECL_EXTERNAL (newdecl) = 1;
 	  /* For now, only warn with explicit -Wdeprecated.  */
-	  if (global_options_set.x_warn_deprecated
-	      && warning_at (DECL_SOURCE_LOCATION (newdecl), OPT_Wdeprecated,
-			     "redundant redeclaration of %<constexpr%> static "
-			     "data member %qD", newdecl))
-	    inform (DECL_SOURCE_LOCATION (olddecl),
-		    "previous declaration of %qD", olddecl);
+	  if (global_options_set.x_warn_deprecated)
+	    {
+	      auto_diagnostic_group d;
+	      if (warning_at (DECL_SOURCE_LOCATION (newdecl), OPT_Wdeprecated,
+				"redundant redeclaration of %<constexpr%> "
+				"static data member %qD", newdecl))
+		inform (DECL_SOURCE_LOCATION (olddecl),
+			  "previous declaration of %qD", olddecl);
+	    }
 	  return NULL;
 	}
 
@@ -4753,6 +4768,7 @@ warn_misplaced_attr_for_class_type (source_location location,
 {
   gcc_assert (OVERLOAD_TYPE_P (class_type));
 
+  auto_diagnostic_group d;
   if (warning_at (location, OPT_Wattributes,
 		  "attribute ignored in declaration "
 		  "of %q#T", class_type))
diff --git a/gcc/cp/decl2.c b/gcc/cp/decl2.c
index d67ced097daf..a5ad0eed3ad6 100644
--- a/gcc/cp/decl2.c
+++ b/gcc/cp/decl2.c
@@ -764,6 +764,7 @@ finish_static_data_member_decl (tree decl,
 	 t = CP_TYPE_CONTEXT (t))
       if (TYPE_UNNAMED_P (t))
 	{
+	  auto_diagnostic_group d;
 	  if (permerror (DECL_SOURCE_LOCATION (decl),
 			 "static data member %qD in unnamed class", decl))
 	    inform (DECL_SOURCE_LOCATION (TYPE_NAME (t)),
@@ -4287,6 +4288,7 @@ no_linkage_error (tree decl)
   else if (TYPE_UNNAMED_P (t))
     {
       bool d = false;
+      auto_diagnostic_group grp;
       if (cxx_dialect >= cxx11)
 	d = permerror (DECL_SOURCE_LOCATION (decl), "%q#D, declared using "
 		       "unnamed type, is used but never defined", decl);
@@ -5208,6 +5210,7 @@ cp_warn_deprecated_use (tree decl, tsubst_flags_t complain)
       && DECL_NONSTATIC_MEMBER_FUNCTION_P (decl)
       && copy_fn_p (decl))
     {
+      auto_diagnostic_group d;
       /* Don't warn about system library classes (c++/86342).  */
       if (!DECL_IN_SYSTEM_HEADER (decl))
 	warned = warning (OPT_Wdeprecated_copy,
diff --git a/gcc/cp/error.c b/gcc/cp/error.c
index 355a5e82f150..452ecb954677 100644
--- a/gcc/cp/error.c
+++ b/gcc/cp/error.c
@@ -4270,12 +4270,14 @@ qualified_name_lookup_error (tree scope, tree name,
     }
   else if (scope != global_namespace)
     {
+      auto_diagnostic_group d;
       error_at (location, "%qD is not a member of %qD", name, scope);
       if (!suggest_alternative_in_explicit_scope (location, name, scope))
 	suggest_alternatives_for (location, name, false);
     }
   else
     {
+      auto_diagnostic_group d;
       error_at (location, "%<::%D%> has not been declared", name);
       suggest_alternatives_for (location, name, true);
     }
diff --git a/gcc/cp/friend.c b/gcc/cp/friend.c
index 2c9c12fab4a9..ce85a806620c 100644
--- a/gcc/cp/friend.c
+++ b/gcc/cp/friend.c
@@ -304,6 +304,7 @@ make_friend_class (tree type, tree friend_type, bool complain)
       if (TYPE_TEMPLATE_INFO (friend_type)
 	  && !PRIMARY_TEMPLATE_P (TYPE_TI_TEMPLATE (friend_type)))
 	{
+	  auto_diagnostic_group d;
 	  error ("%qT is not a template", friend_type);
 	  inform (location_of (friend_type), "previous declaration here");
 	  if (TYPE_CLASS_SCOPE_P (friend_type)
@@ -384,6 +385,7 @@ make_friend_class (tree type, tree friend_type, bool complain)
 		}
 	      if (template_member_p && !DECL_CLASS_TEMPLATE_P (decl))
 		{
+		  auto_diagnostic_group d;
 		  error ("%qT is not a member class template of %qT",
 			 name, ctype);
 		  inform (DECL_SOURCE_LOCATION (decl),
@@ -393,6 +395,7 @@ make_friend_class (tree type, tree friend_type, bool complain)
 	      if (!template_member_p && (TREE_CODE (decl) != TYPE_DECL
 					 || !CLASS_TYPE_P (TREE_TYPE (decl))))
 		{
+		  auto_diagnostic_group d;
 		  error ("%qT is not a nested class of %qT",
 			 name, ctype);
 		  inform (DECL_SOURCE_LOCATION (decl),
@@ -636,6 +639,7 @@ do_friend (tree ctype, tree declarator, tree decl,
 	      static int explained;
 	      bool warned;
 
+	      auto_diagnostic_group d;
 	      warned = warning (OPT_Wnon_template_friend, "friend declaration "
 				"%q#D declares a non-template function", decl);
 	      if (! explained && warned)
diff --git a/gcc/cp/init.c b/gcc/cp/init.c
index 94f8fdd7bd98..15046b4257bc 100644
--- a/gcc/cp/init.c
+++ b/gcc/cp/init.c
@@ -915,6 +915,7 @@ perform_member_init (tree member, tree init)
 	    {
 	      /* TYPE_NEEDS_CONSTRUCTING can be set just because we have a
 		 vtable; still give this diagnostic.  */
+	      auto_diagnostic_group d;
 	      if (permerror (DECL_SOURCE_LOCATION (current_function_decl),
 			     "uninitialized const member in %q#T", type))
 		inform (DECL_SOURCE_LOCATION (member),
@@ -932,6 +933,7 @@ perform_member_init (tree member, tree init)
 	  /* member traversal: note it leaves init NULL */
 	  if (TYPE_REF_P (type))
 	    {
+	      auto_diagnostic_group d;
 	      if (permerror (DECL_SOURCE_LOCATION (current_function_decl),
 			     "uninitialized reference member in %q#T", type))
 		inform (DECL_SOURCE_LOCATION (member),
@@ -939,6 +941,7 @@ perform_member_init (tree member, tree init)
 	    }
 	  else if (CP_TYPE_CONST_P (type))
 	    {
+	      auto_diagnostic_group d;
 	      if (permerror (DECL_SOURCE_LOCATION (current_function_decl),
 			     "uninitialized const member in %q#T", type))
 		  inform (DECL_SOURCE_LOCATION (member),
@@ -3255,6 +3258,7 @@ build_new_1 (vec<tree, va_gc> **placement, tree type, tree nelts,
 	  || CP_DECL_CONTEXT (alloc_fn) == global_namespace)
       && !aligned_allocation_fn_p (alloc_fn))
     {
+      auto_diagnostic_group d;
       if (warning (OPT_Waligned_new_, "%<new%> of type %qT with extended "
 		   "alignment %d", elt_type, TYPE_ALIGN_UNIT (elt_type)))
 	{
@@ -3831,16 +3835,19 @@ build_vec_delete_1 (tree base, tree maxindex, tree type,
 
   if (!COMPLETE_TYPE_P (type))
     {
-      if ((complain & tf_warning)
-	  && warning (OPT_Wdelete_incomplete,
-		      "possible problem detected in invocation of "
-		      "delete [] operator:"))
-       {
-         cxx_incomplete_type_diagnostic (base, type, DK_WARNING);
-         inform (input_location, "neither the destructor nor the "
-                 "class-specific operator delete [] will be called, "
-                 "even if they are declared when the class is defined");
-       }
+      if (complain & tf_warning)
+	{
+	  auto_diagnostic_group d;
+	  if (warning (OPT_Wdelete_incomplete,
+			 "possible problem detected in invocation of "
+			 "delete [] operator:"))
+	    {
+	      cxx_incomplete_type_diagnostic (base, type, DK_WARNING);
+	      inform (input_location, "neither the destructor nor the "
+			"class-specific operator delete [] will be called, "
+			"even if they are declared when the class is defined");
+	    }
+	}
       /* This size won't actually be used.  */
       size_exp = size_one_node;
       goto no_destructor;
@@ -4712,16 +4719,19 @@ build_delete (tree otype, tree addr, special_function_kind auto_delete,
 	  complete_type (type);
 	  if (!COMPLETE_TYPE_P (type))
 	    {
-	      if ((complain & tf_warning)
-		  && warning (OPT_Wdelete_incomplete,
-			      "possible problem detected in invocation of "
-			      "delete operator:"))
+	      if (complain & tf_warning)
 		{
-		  cxx_incomplete_type_diagnostic (addr, type, DK_WARNING);
-		  inform (input_location,
-			  "neither the destructor nor the class-specific "
-			  "operator delete will be called, even if they are "
-			  "declared when the class is defined");
+		  auto_diagnostic_group d;
+		  if (warning (OPT_Wdelete_incomplete,
+				 "possible problem detected in invocation of "
+				 "delete operator:"))
+		    {
+		      cxx_incomplete_type_diagnostic (addr, type, DK_WARNING);
+		      inform (input_location,
+				"neither the destructor nor the class-specific "
+				"operator delete will be called, even if they "
+				"are declared when the class is defined");
+		    }
 		}
 	    }
 	  else if (deleting && warn_delnonvdtor
diff --git a/gcc/cp/lex.c b/gcc/cp/lex.c
index bd5d507e97b8..47b99c3c4692 100644
--- a/gcc/cp/lex.c
+++ b/gcc/cp/lex.c
@@ -499,6 +499,7 @@ unqualified_name_lookup_error (tree name, location_t loc)
     {
       if (!objc_diagnose_private_ivar (name))
 	{
+	  auto_diagnostic_group d;
 	  error_at (loc, "%qD was not declared in this scope", name);
 	  suggest_alternatives_for (loc, name, true);
 	}
diff --git a/gcc/cp/name-lookup.c b/gcc/cp/name-lookup.c
index 3ba76447f98c..8c7f68522da4 100644
--- a/gcc/cp/name-lookup.c
+++ b/gcc/cp/name-lookup.c
@@ -2556,6 +2556,7 @@ check_extern_c_conflict (tree decl)
 
       if (mismatch)
 	{
+	  auto_diagnostic_group d;
 	  pedwarn (input_location, 0,
 		   "conflicting C language linkage declaration %q#D", decl);
 	  inform (DECL_SOURCE_LOCATION (old),
@@ -2604,6 +2605,15 @@ c_linkage_bindings (tree name)
   return NULL_TREE;
 }
 
+/* Subroutine of check_local_shadow.  */
+
+static void
+inform_shadowed (tree shadowed)
+{
+  inform (DECL_SOURCE_LOCATION (shadowed),
+	  "shadowed declaration is here");
+}
+
 /* DECL is being declared at a local scope.  Emit suitable shadow
    warnings.  */
 
@@ -2631,7 +2641,6 @@ check_local_shadow (tree decl)
       old_scope = binding->scope;
     }
 
-  tree shadowed = NULL_TREE;
   if (old
       && (TREE_CODE (old) == PARM_DECL
 	  || VAR_P (old)
@@ -2702,6 +2711,7 @@ check_local_shadow (tree decl)
 	       && old_scope == current_binding_level->level_chain
 	       && (old_scope->kind == sk_cond || old_scope->kind == sk_for))
 	{
+	  auto_diagnostic_group d;
 	  error ("redeclaration of %q#D", decl);
 	  inform (DECL_SOURCE_LOCATION (old),
 		  "%q#D previously declared here", old);
@@ -2724,6 +2734,7 @@ check_local_shadow (tree decl)
 		       || current_binding_level->level_chain->kind == sk_catch)
 		   && in_function_try_handler))
 	{
+	  auto_diagnostic_group d;
 	  if (permerror (input_location, "redeclaration of %q#D", decl))
 	    inform (DECL_SOURCE_LOCATION (old),
 		    "%q#D previously declared here", old);
@@ -2764,11 +2775,9 @@ check_local_shadow (tree decl)
       else
 	msg = "declaration of %qD shadows a previous local";
 
+      auto_diagnostic_group d;
       if (warning_at (input_location, warning_code, msg, decl))
-	{
-	  shadowed = old;
-	  goto inform_shadowed;
-	}
+	inform_shadowed (old);
       return;
     }
 
@@ -2793,14 +2802,12 @@ check_local_shadow (tree decl)
 	    || TYPE_PTRFN_P (TREE_TYPE (decl))
 	    || TYPE_PTRMEMFUNC_P (TREE_TYPE (decl)))
 	  {
+	    auto_diagnostic_group d;
 	    if (warning_at (input_location, OPT_Wshadow,
 			    "declaration of %qD shadows a member of %qT",
 			    decl, current_nonlambda_class_type ())
 		&& DECL_P (member))
-	      {
-		shadowed = member;
-		goto inform_shadowed;
-	      }
+	      inform_shadowed (member);
 	  }
 	return;
       }
@@ -2815,20 +2822,15 @@ check_local_shadow (tree decl)
       && !instantiating_current_function_p ())
     /* XXX shadow warnings in outer-more namespaces */
     {
+      auto_diagnostic_group d;
       if (warning_at (input_location, OPT_Wshadow,
 		      "declaration of %qD shadows a global declaration",
 		      decl))
-	{
-	  shadowed = old;
-	  goto inform_shadowed;
-	}
+	inform_shadowed (old);
       return;
     }
 
   return;
-
- inform_shadowed:
-  inform (DECL_SOURCE_LOCATION (shadowed), "shadowed declaration is here");
 }
 
 /* DECL is being pushed inside function CTX.  Set its context, if
@@ -2954,6 +2956,7 @@ set_local_extern_decl_linkage (tree decl, bool shadowed)
 		       && !comptypes (TREE_TYPE (decl), TREE_TYPE (other),
 				      COMPARE_REDECLARATION)))
 	    {
+	      auto_diagnostic_group d;
 	      if (permerror (DECL_SOURCE_LOCATION (decl),
 			     "local external declaration %q#D", decl))
 		inform (DECL_SOURCE_LOCATION (other),
diff --git a/gcc/cp/parser.c b/gcc/cp/parser.c
index 8cfcd150705f..aa5286b24ccb 100644
--- a/gcc/cp/parser.c
+++ b/gcc/cp/parser.c
@@ -3280,6 +3280,7 @@ cp_parser_diagnose_invalid_type_name (cp_parser *parser, tree id,
   to specify an argument list. Emit a useful error message.  */
   if (DECL_TYPE_TEMPLATE_P (decl))
     {
+      auto_diagnostic_group d;
       error_at (location,
 		"invalid use of template-name %qE without an argument list",
 		decl);
@@ -3296,6 +3297,7 @@ cp_parser_diagnose_invalid_type_name (cp_parser *parser, tree id,
   else if (!parser->scope)
     {
       /* Issue an error message.  */
+      auto_diagnostic_group d;
       name_hint hint;
       if (TREE_CODE (id) == IDENTIFIER_NODE)
 	hint = lookup_name_fuzzy (id, FUZZY_LOOKUP_TYPENAME, location);
@@ -3370,6 +3372,7 @@ cp_parser_diagnose_invalid_type_name (cp_parser *parser, tree id,
     {
       if (TREE_CODE (parser->scope) == NAMESPACE_DECL)
 	{
+	  auto_diagnostic_group d;
 	  if (cp_lexer_next_token_is (parser->lexer, CPP_LESS))
 	    error_at (location_of (id),
 		      "%qE in namespace %qE does not name a template type",
@@ -3392,6 +3395,7 @@ cp_parser_diagnose_invalid_type_name (cp_parser *parser, tree id,
 	       && constructor_name_p (id, parser->scope))
 	{
 	  /* A<T>::A<T>() */
+	  auto_diagnostic_group d;
 	  error_at (location, "%<%T::%E%> names the constructor, not"
 		    " the type", parser->scope, id);
 	  if (cp_lexer_next_token_is (parser->lexer, CPP_LESS))
@@ -3417,6 +3421,7 @@ cp_parser_diagnose_invalid_type_name (cp_parser *parser, tree id,
 	}
       else if (TYPE_P (parser->scope))
 	{
+	  auto_diagnostic_group d;
 	  if (!COMPLETE_TYPE_P (parser->scope))
 	    cxx_incomplete_type_error (location_of (id), NULL_TREE,
 				       parser->scope);
@@ -18615,6 +18620,7 @@ cp_parser_namespace_name (cp_parser* parser)
     {
       if (!cp_parser_uncommitted_to_tentative_parse_p (parser))
 	{
+	  auto_diagnostic_group d;
 	  error_at (token->location, "%qD is not a namespace-name", identifier);
 	  if (namespace_decl == error_mark_node
 	      && parser->scope && TREE_CODE (parser->scope) == NAMESPACE_DECL)
diff --git a/gcc/cp/pt.c b/gcc/cp/pt.c
index cbb7b8ea853d..efed9a1bf60e 100644
--- a/gcc/cp/pt.c
+++ b/gcc/cp/pt.c
@@ -800,6 +800,7 @@ check_specialization_namespace (tree tmpl)
     return true;
   else
     {
+      auto_diagnostic_group d;
       if (permerror (input_location,
 		     "specialization of %qD in different namespace", tmpl))
 	inform (DECL_SOURCE_LOCATION (tmpl),
@@ -2592,6 +2593,7 @@ check_template_variable (tree decl)
     }
   if (template_header_count > wanted)
     {
+      auto_diagnostic_group d;
       bool warned = pedwarn (DECL_SOURCE_LOCATION (decl), 0,
 			     "too many template headers for %qD "
 	                     "(should be %d)",
@@ -2724,6 +2726,7 @@ warn_spec_missing_attributes (tree tmpl, tree spec, tree attrlist)
   if (!nattrs)
     return;
 
+  auto_diagnostic_group d;
   if (warning_at (DECL_SOURCE_LOCATION (spec), OPT_Wmissing_attributes,
 		  "explicit specialization %q#D may be missing attributes",
 		  spec))
@@ -3070,6 +3073,7 @@ check_explicit_specialization (tree declarator,
 	  if (TREE_CODE (decl) == FUNCTION_DECL
 	      && DECL_HIDDEN_FRIEND_P (tmpl))
 	    {
+	      auto_diagnostic_group d;
 	      if (pedwarn (DECL_SOURCE_LOCATION (decl), 0,
 			   "friend declaration %qD is not visible to "
 			   "explicit specialization", tmpl))
@@ -4891,6 +4895,7 @@ process_partial_specialization (tree decl)
 	   && TMPL_ARGS_DEPTH (specargs) == 1
 	   && !get_partial_spec_bindings (maintmpl, maintmpl, specargs))
     {
+      auto_diagnostic_group d;
       if (permerror (input_location, "partial specialization %qD is not "
 		     "more specialized than", decl))
 	inform (DECL_SOURCE_LOCATION (maintmpl), "primary template %qD",
@@ -9354,6 +9359,7 @@ lookup_template_class_1 (tree d1, tree arglist, tree in_decl, tree context,
         {
           if (complain & tf_error)
             {
+	      auto_diagnostic_group d;
               error ("template constraint failure");
               diagnose_constraints (input_location, gen_tmpl, arglist);
             }
@@ -9712,6 +9718,7 @@ finish_template_variable (tree var, tsubst_flags_t complain)
     {
       if (complain & tf_error)
 	{
+	  auto_diagnostic_group d;
 	  error ("use of invalid variable template %qE", var);
 	  diagnose_constraints (location_of (var), templ, arglist);
 	}
@@ -26888,6 +26895,7 @@ do_auto_deduction (tree type, tree init, tree auto_node,
           {
             if (complain & tf_warning_or_error)
               {
+		auto_diagnostic_group d;
                 switch (context)
                   {
                   case adc_unspecified:
diff --git a/gcc/cp/search.c b/gcc/cp/search.c
index c2860b0dc9a8..d700fe328f4b 100644
--- a/gcc/cp/search.c
+++ b/gcc/cp/search.c
@@ -1911,6 +1911,7 @@ check_final_overrider (tree overrider, tree basefn)
 	/* GNU extension, allow trivial pointer conversions such as
 	   converting to void *, or qualification conversion.  */
 	{
+	  auto_diagnostic_group d;
 	  if (pedwarn (DECL_SOURCE_LOCATION (overrider), 0,
 		       "invalid covariant return type for %q#D", overrider))
 	    inform (DECL_SOURCE_LOCATION (basefn),
@@ -1927,12 +1928,14 @@ check_final_overrider (tree overrider, tree basefn)
     {
       if (fail == 1)
 	{
+	  auto_diagnostic_group d;
 	  error ("invalid covariant return type for %q+#D", overrider);
 	  inform (DECL_SOURCE_LOCATION (basefn),
 		  "overridden function is %q#D", basefn);
 	}
       else
 	{
+	  auto_diagnostic_group d;
 	  error ("conflicting return type specified for %q+#D", overrider);
 	  inform (DECL_SOURCE_LOCATION (basefn),
 		  "overridden function is %q#D", basefn);
@@ -1949,6 +1952,7 @@ check_final_overrider (tree overrider, tree basefn)
 
   if (!comp_except_specs (base_throw, over_throw, ce_derived))
     {
+      auto_diagnostic_group d;
       error ("looser throw specifier for %q+#F", overrider);
       inform (DECL_SOURCE_LOCATION (basefn),
 	      "overridden function is %q#F", basefn);
@@ -1962,6 +1966,7 @@ check_final_overrider (tree overrider, tree basefn)
       && !tx_safe_fn_type_p (base_type)
       && !tx_safe_fn_type_p (over_type))
     {
+      auto_diagnostic_group d;
       error ("conflicting type attributes specified for %q+#D", overrider);
       inform (DECL_SOURCE_LOCATION (basefn),
 	      "overridden function is %q#D", basefn);
@@ -1978,6 +1983,7 @@ check_final_overrider (tree overrider, tree basefn)
       && !lookup_attribute ("transaction_safe_dynamic",
 			    DECL_ATTRIBUTES (basefn)))
     {
+      auto_diagnostic_group d;
       error_at (DECL_SOURCE_LOCATION (overrider),
 		"%qD declared %<transaction_safe_dynamic%>", overrider);
       inform (DECL_SOURCE_LOCATION (basefn),
@@ -1988,6 +1994,7 @@ check_final_overrider (tree overrider, tree basefn)
     {
       if (DECL_DELETED_FN (overrider))
 	{
+	  auto_diagnostic_group d;
 	  error ("deleted function %q+D overriding non-deleted function",
 		 overrider);
 	  inform (DECL_SOURCE_LOCATION (basefn),
@@ -1996,6 +2003,7 @@ check_final_overrider (tree overrider, tree basefn)
 	}
       else
 	{
+	  auto_diagnostic_group d;
 	  error ("non-deleted function %q+D overriding deleted function",
 		 overrider);
 	  inform (DECL_SOURCE_LOCATION (basefn),
@@ -2005,6 +2013,7 @@ check_final_overrider (tree overrider, tree basefn)
     }
   if (DECL_FINAL_P (basefn))
     {
+      auto_diagnostic_group d;
       error ("virtual function %q+D overriding final function", overrider);
       inform (DECL_SOURCE_LOCATION (basefn),
 	      "overridden function is %qD", basefn);
@@ -2089,6 +2098,7 @@ look_for_overrides_r (tree type, tree fndecl)
 	{
 	  /* A static member function cannot match an inherited
 	     virtual member function.  */
+	  auto_diagnostic_group d;
 	  error ("%q+#D cannot be declared", fndecl);
 	  error ("  since %q+#D declared in base class", fn);
 	}
diff --git a/gcc/cp/tree.c b/gcc/cp/tree.c
index 1cf3269d8806..8a1d2993f946 100644
--- a/gcc/cp/tree.c
+++ b/gcc/cp/tree.c
@@ -4031,6 +4031,7 @@ maybe_warn_parm_abi (tree t, location_t loc)
       && classtype_has_non_deleted_move_ctor (t))
     {
       bool w;
+      auto_diagnostic_group d;
       if (flag_abi_version > 12)
 	w = warning_at (loc, OPT_Wabi, "-fabi-version=13 (GCC 8.2) fixes the "
 			"calling convention for %qT, which was accidentally "
@@ -4043,6 +4044,7 @@ maybe_warn_parm_abi (tree t, location_t loc)
       return;
     }
 
+  auto_diagnostic_group d;
   if (warning_at (loc, OPT_Wabi, "the calling convention for %qT changes in "
 		  "-fabi-version=13 (GCC 8.2)", t))
     inform (location_of (t), " because all of its copy and move "
diff --git a/gcc/cp/typeck.c b/gcc/cp/typeck.c
index 8c13ae9b19ba..99be38ed8f86 100644
--- a/gcc/cp/typeck.c
+++ b/gcc/cp/typeck.c
@@ -1691,6 +1691,7 @@ cxx_sizeof_expr (tree e, tsubst_flags_t complain)
       && DECL_ARRAY_PARAMETER_P (e)
       && (complain & tf_warning))
     {
+      auto_diagnostic_group d;
       if (warning (OPT_Wsizeof_array_argument, "%<sizeof%> on array function "
 		   "parameter %qE will return size of %qT", e, TREE_TYPE (e)))
 	inform (DECL_SOURCE_LOCATION (e), "declared here");
@@ -3699,6 +3700,7 @@ cp_build_function_call_vec (tree function, vec<tree, va_gc> **params,
           && (complain & tf_error)
           && !constraints_satisfied_p (function))
         {
+          auto_diagnostic_group d;
           error ("cannot call function %qD", function);
           location_t loc = DECL_SOURCE_LOCATION (function);
           diagnose_constraints (loc, function, NULL_TREE);
@@ -4467,13 +4469,16 @@ cp_build_binary_op (location_t location,
 		   && DECL_ARRAY_PARAMETER_P (first_arg)
 		   && warn_sizeof_array_argument)
 	      && (complain & tf_warning))
-	    if (warning_at (location, OPT_Wsizeof_pointer_div,
-			    "division %<sizeof (%T) / sizeof (%T)%> does "
-			    "not compute the number of array elements",
+	    {
+	      auto_diagnostic_group d;
+	      if (warning_at (location, OPT_Wsizeof_pointer_div,
+				"division %<sizeof (%T) / sizeof (%T)%> does "
+				"not compute the number of array elements",
 			    type0, type1))
-	      if (DECL_P (first_arg))
-		inform (DECL_SOURCE_LOCATION (first_arg),
-			"first %<sizeof%> operand was declared here");
+		if (DECL_P (first_arg))
+		  inform (DECL_SOURCE_LOCATION (first_arg),
+			    "first %<sizeof%> operand was declared here");
+	    }
 	}
 
       if ((code0 == INTEGER_TYPE || code0 == REAL_TYPE
@@ -4766,12 +4771,15 @@ cp_build_binary_op (location_t location,
 	  else
 	    result_type = type0;
 
-	  if (char_type_p (TREE_TYPE (orig_op1))
-	      && warning (OPT_Wpointer_compare,
-			  "comparison between pointer and zero character "
-			  "constant"))
-	    inform (input_location,
-		    "did you mean to dereference the pointer?");
+	  if (char_type_p (TREE_TYPE (orig_op1)))
+	    {
+	      auto_diagnostic_group d;
+	      if (warning (OPT_Wpointer_compare,
+			     "comparison between pointer and zero character "
+			     "constant"))
+		inform (input_location,
+			  "did you mean to dereference the pointer?");
+	    }
 	  warn_for_null_address (location, op0, complain);
 	}
       else if (((code1 == POINTER_TYPE || TYPE_PTRDATAMEM_P (type1))
@@ -4786,12 +4794,15 @@ cp_build_binary_op (location_t location,
 	  else
 	    result_type = type1;
 
-	  if (char_type_p (TREE_TYPE (orig_op0))
-	      && warning (OPT_Wpointer_compare,
-			  "comparison between pointer and zero character "
-			  "constant"))
-	    inform (input_location,
-		    "did you mean to dereference the pointer?");
+	  if (char_type_p (TREE_TYPE (orig_op0)))
+	    {
+	      auto_diagnostic_group d;
+	      if (warning (OPT_Wpointer_compare,
+			     "comparison between pointer and zero character "
+			     "constant"))
+		inform (input_location,
+			"did you mean to dereference the pointer?");
+	    }
 	  warn_for_null_address (location, op1, complain);
 	}
       else if ((code0 == POINTER_TYPE && code1 == POINTER_TYPE)
@@ -8807,6 +8818,7 @@ convert_for_assignment (tree type, tree rhs,
 		}
 	      else if (fndecl)
 		{
+		  auto_diagnostic_group d;
 		  location_t loc = cp_expr_location (rhs);
 		  range_label_for_type_mismatch rhs_label (rhstype, type);
 		  range_label *label = &rhs_label;
@@ -9087,6 +9099,7 @@ maybe_warn_about_returning_address_of_local (tree retval)
 	   || TREE_PUBLIC (whats_returned)))
     {
       bool w = false;
+      auto_diagnostic_group d;
       if (TYPE_REF_P (valtype))
 	w = warning_at (loc, OPT_Wreturn_local_addr,
 			"reference to local variable %qD returned",
diff --git a/gcc/cp/typeck2.c b/gcc/cp/typeck2.c
index 674d08762b5a..f42f0c2bf074 100644
--- a/gcc/cp/typeck2.c
+++ b/gcc/cp/typeck2.c
@@ -315,6 +315,7 @@ abstract_virtuals_error_sfinae (tree decl, tree type, abstract_class_use use,
   if (!(complain & tf_error))
     return 1;
 
+  auto_diagnostic_group d;
   if (decl)
     {
       if (VAR_P (decl))
@@ -983,6 +984,7 @@ check_narrowing (tree type, tree init, tsubst_flags_t complain, bool const_only)
 	{
 	  if (complain & tf_warning_or_error)
 	    {
+	      auto_diagnostic_group d;
 	      if ((!almost_ok || pedantic)
 		  && pedwarn (loc, OPT_Wnarrowing,
 			      "narrowing conversion of %qE from %qH to %qI",
diff --git a/gcc/diagnostic-core.h b/gcc/diagnostic-core.h
index aa5807e17e02..e4ebe005ede5 100644
--- a/gcc/diagnostic-core.h
+++ b/gcc/diagnostic-core.h
@@ -36,6 +36,15 @@ typedef enum
   DK_POP
 } diagnostic_t;
 
+/* RAII-style class for grouping related diagnostics.  */
+
+class auto_diagnostic_group
+{
+ public:
+  auto_diagnostic_group ();
+  ~auto_diagnostic_group ();
+};
+
 extern const char *progname;
 
 extern const char *trim_filename (const char *);
diff --git a/gcc/diagnostic.c b/gcc/diagnostic.c
index 7e8bcf52dc1e..aae0934d21a6 100644
--- a/gcc/diagnostic.c
+++ b/gcc/diagnostic.c
@@ -180,6 +180,10 @@ diagnostic_initialize (diagnostic_context *context, int n_opts)
   context->show_ruler_p = false;
   context->parseable_fixits_p = false;
   context->edit_context_ptr = NULL;
+  context->diagnostic_group_nesting_depth = 0;
+  context->diagnostic_group_emission_count = 0;
+  context->begin_group_cb = NULL;
+  context->end_group_cb = NULL;
 }
 
 /* Maybe initialize the color support. We require clients to do this
@@ -986,6 +990,14 @@ diagnostic_report_diagnostic (diagnostic_context *context,
   else
     ++diagnostic_kind_count (context, diagnostic->kind);
 
+  /* Is this the initial diagnostic within the stack of groups?  */
+  if (context->diagnostic_group_emission_count == 0)
+    {
+      if (context->begin_group_cb)
+	context->begin_group_cb (context);
+    }
+  context->diagnostic_group_emission_count++;
+
   diagnostic->message.x_data = &diagnostic->x_data;
   diagnostic->x_data = NULL;
   pp_format (context->printer, &diagnostic->message);
@@ -1146,6 +1158,7 @@ bool
 emit_diagnostic (diagnostic_t kind, location_t location, int opt,
 		 const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, location);
@@ -1169,6 +1182,7 @@ emit_diagnostic_valist (diagnostic_t kind, location_t location, int opt,
 void
 inform (location_t location, const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, location);
@@ -1182,6 +1196,7 @@ inform (rich_location *richloc, const char *gmsgid, ...)
 {
   gcc_assert (richloc);
 
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   diagnostic_impl (richloc, -1, gmsgid, &ap, DK_NOTE);
@@ -1196,6 +1211,7 @@ inform_n (location_t location, unsigned HOST_WIDE_INT n,
 {
   va_list ap;
   va_start (ap, plural_gmsgid);
+  auto_diagnostic_group d;
   rich_location richloc (line_table, location);
   diagnostic_n_impl (&richloc, -1, n, singular_gmsgid, plural_gmsgid,
 		     &ap, DK_NOTE);
@@ -1208,6 +1224,7 @@ inform_n (location_t location, unsigned HOST_WIDE_INT n,
 bool
 warning (int opt, const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, input_location);
@@ -1223,6 +1240,7 @@ warning (int opt, const char *gmsgid, ...)
 bool
 warning_at (location_t location, int opt, const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, location);
@@ -1238,6 +1256,7 @@ warning_at (rich_location *richloc, int opt, const char *gmsgid, ...)
 {
   gcc_assert (richloc);
 
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   bool ret = diagnostic_impl (richloc, opt, gmsgid, &ap, DK_WARNING);
@@ -1253,6 +1272,7 @@ warning_n (rich_location *richloc, int opt, unsigned HOST_WIDE_INT n,
 {
   gcc_assert (richloc);
 
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, plural_gmsgid);
   bool ret = diagnostic_n_impl (richloc, opt, n,
@@ -1270,6 +1290,7 @@ bool
 warning_n (location_t location, int opt, unsigned HOST_WIDE_INT n,
 	   const char *singular_gmsgid, const char *plural_gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, plural_gmsgid);
   rich_location richloc (line_table, location);
@@ -1296,6 +1317,7 @@ warning_n (location_t location, int opt, unsigned HOST_WIDE_INT n,
 bool
 pedwarn (location_t location, int opt, const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, location);
@@ -1311,6 +1333,7 @@ pedwarn (rich_location *richloc, int opt, const char *gmsgid, ...)
 {
   gcc_assert (richloc);
 
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   bool ret = diagnostic_impl (richloc, opt, gmsgid, &ap, DK_PEDWARN);
@@ -1328,6 +1351,7 @@ pedwarn (rich_location *richloc, int opt, const char *gmsgid, ...)
 bool
 permerror (location_t location, const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, location);
@@ -1343,6 +1367,7 @@ permerror (rich_location *richloc, const char *gmsgid, ...)
 {
   gcc_assert (richloc);
 
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   bool ret = diagnostic_impl (richloc, -1, gmsgid, &ap, DK_PERMERROR);
@@ -1355,6 +1380,7 @@ permerror (rich_location *richloc, const char *gmsgid, ...)
 void
 error (const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, input_location);
@@ -1368,6 +1394,7 @@ void
 error_n (location_t location, unsigned HOST_WIDE_INT n,
 	 const char *singular_gmsgid, const char *plural_gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, plural_gmsgid);
   rich_location richloc (line_table, location);
@@ -1380,6 +1407,7 @@ error_n (location_t location, unsigned HOST_WIDE_INT n,
 void
 error_at (location_t loc, const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, loc);
@@ -1394,6 +1422,7 @@ error_at (rich_location *richloc, const char *gmsgid, ...)
 {
   gcc_assert (richloc);
 
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   diagnostic_impl (richloc, -1, gmsgid, &ap, DK_ERROR);
@@ -1406,6 +1435,7 @@ error_at (rich_location *richloc, const char *gmsgid, ...)
 void
 sorry (const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, input_location);
@@ -1427,6 +1457,7 @@ seen_error (void)
 void
 fatal_error (location_t loc, const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, loc);
@@ -1443,6 +1474,7 @@ fatal_error (location_t loc, const char *gmsgid, ...)
 void
 internal_error (const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, input_location);
@@ -1458,6 +1490,7 @@ internal_error (const char *gmsgid, ...)
 void
 internal_error_no_backtrace (const char *gmsgid, ...)
 {
+  auto_diagnostic_group d;
   va_list ap;
   va_start (ap, gmsgid);
   rich_location richloc (line_table, input_location);
@@ -1515,6 +1548,33 @@ fancy_abort (const char *file, int line, const char *function)
   internal_error ("in %s, at %s:%d", function, trim_filename (file), line);
 }
 
+/* class auto_diagnostic_group.  */
+
+/* Constructor: "push" this group into global_dc.  */
+
+auto_diagnostic_group::auto_diagnostic_group ()
+{
+  global_dc->diagnostic_group_nesting_depth++;
+}
+
+/* Destructor: "pop" this group from global_dc.  */
+
+auto_diagnostic_group::~auto_diagnostic_group ()
+{
+  if (--global_dc->diagnostic_group_nesting_depth == 0)
+    {
+      /* Handle the case where we've popped the final diagnostic group.
+	 If any diagnostics were emitted, give the context a chance
+	 to do something.  */
+      if (global_dc->diagnostic_group_emission_count > 0)
+	{
+	  if (global_dc->end_group_cb)
+	    global_dc->end_group_cb (global_dc);
+	}
+      global_dc->diagnostic_group_emission_count = 0;
+    }
+}
+
 /* Really call the system 'abort'.  This has to go right at the end of
    this file, so that there are no functions after it that call abort
    and get the system abort instead of our macro.  */
diff --git a/gcc/diagnostic.h b/gcc/diagnostic.h
index fe3130bdf9d1..34ea03bb6947 100644
--- a/gcc/diagnostic.h
+++ b/gcc/diagnostic.h
@@ -222,6 +222,23 @@ struct diagnostic_context
   /* If non-NULL, an edit_context to which fix-it hints should be
      applied, for generating patches.  */
   edit_context *edit_context_ptr;
+
+  /* How many diagnostic_group instances are currently alive.  */
+  int diagnostic_group_nesting_depth;
+
+  /* How many diagnostics have been emitted since the bottommost
+     diagnostic_group was pushed.  */
+  int diagnostic_group_emission_count;
+
+  /* Optional callbacks for handling diagnostic groups.  */
+
+  /* If non-NULL, this will be called immediately before the first
+     time a diagnostic is emitted within a stack of groups.  */
+  void (*begin_group_cb) (diagnostic_context * context);
+
+  /* If non-NULL, this will be called when a stack of groups is
+     popped if any diagnostics were emitted within that group.  */
+  void (*end_group_cb) (diagnostic_context * context);
 };
 
 static inline void
diff --git a/gcc/gimple-ssa-isolate-paths.c b/gcc/gimple-ssa-isolate-paths.c
index 131705d18279..e1fab61bedab 100644
--- a/gcc/gimple-ssa-isolate-paths.c
+++ b/gcc/gimple-ssa-isolate-paths.c
@@ -421,12 +421,15 @@ find_implicit_erroneous_behavior (void)
 			  if (gimple_return_retval (return_stmt) != lhs)
 			    continue;
 
-			  if (warning_at (gimple_location (use_stmt),
-					  OPT_Wreturn_local_addr,
-					  "function may return address "
-					  "of local variable"))
-			    inform (DECL_SOURCE_LOCATION(valbase),
-				    "declared here");
+			  {
+			    auto_diagnostic_group d;
+			    if (warning_at (gimple_location (use_stmt),
+					      OPT_Wreturn_local_addr,
+					      "function may return address "
+					      "of local variable"))
+			      inform (DECL_SOURCE_LOCATION(valbase),
+					"declared here");
+			  }
 
 			  if (gimple_bb (use_stmt) == bb)
 			    {
@@ -543,10 +546,13 @@ find_explicit_erroneous_behavior (void)
 		      else
 			msg = N_("function may return address of "
 				 "local variable");
-
-		      if (warning_at (gimple_location (stmt),
-				      OPT_Wreturn_local_addr, msg))
-			inform (DECL_SOURCE_LOCATION(valbase), "declared here");
+		      {
+			auto_diagnostic_group d;
+			if (warning_at (gimple_location (stmt),
+					  OPT_Wreturn_local_addr, msg))
+			  inform (DECL_SOURCE_LOCATION(valbase),
+				  "declared here");
+		      }
 		      tree zero = build_zero_cst (TREE_TYPE (val));
 		      gimple_return_set_retval (return_stmt, zero);
 		      update_stmt (stmt);
diff --git a/gcc/gimple-ssa-warn-alloca.c b/gcc/gimple-ssa-warn-alloca.c
index 0331f66844a3..434770772ae7 100644
--- a/gcc/gimple-ssa-warn-alloca.c
+++ b/gcc/gimple-ssa-warn-alloca.c
@@ -532,29 +532,37 @@ pass_walloca::execute (function *fun)
 	    case ALLOCA_OK:
 	      break;
 	    case ALLOCA_BOUND_MAYBE_LARGE:
-	      if (warning_at (loc, wcode,
-			      is_vla ? G_("argument to variable-length array "
-					  "may be too large")
-			      : G_("argument to %<alloca%> may be too large"))
-		  && t.limit != 0)
-		{
-		  print_decu (t.limit, buff);
-		  inform (loc, G_("limit is %wu bytes, but argument "
-				  "may be as large as %s"),
-			  is_vla ? warn_vla_limit : warn_alloca_limit, buff);
-		}
+	      {
+		auto_diagnostic_group d;
+		if (warning_at (loc, wcode,
+				is_vla ? G_("argument to variable-length "
+					    "array may be too large")
+				: G_("argument to %<alloca%> may be too "
+				     "large"))
+		    && t.limit != 0)
+		  {
+		    print_decu (t.limit, buff);
+		    inform (loc, G_("limit is %wu bytes, but argument "
+				    "may be as large as %s"),
+			    is_vla ? warn_vla_limit : warn_alloca_limit, buff);
+		  }
+	      }
 	      break;
 	    case ALLOCA_BOUND_DEFINITELY_LARGE:
-	      if (warning_at (loc, wcode,
-			      is_vla ? G_("argument to variable-length array "
-					  "is too large")
-			      : G_("argument to %<alloca%> is too large"))
-		  && t.limit != 0)
-		{
-		  print_decu (t.limit, buff);
-		  inform (loc, G_("limit is %wu bytes, but argument is %s"),
-			  is_vla ? warn_vla_limit : warn_alloca_limit, buff);
-		}
+	      {
+		auto_diagnostic_group d;
+		if (warning_at (loc, wcode,
+				is_vla ? G_("argument to variable-length"
+					    " array is too large")
+				: G_("argument to %<alloca%> is too large"))
+		    && t.limit != 0)
+		  {
+		    print_decu (t.limit, buff);
+		    inform (loc, G_("limit is %wu bytes, but argument is %s"),
+			      is_vla ? warn_vla_limit : warn_alloca_limit,
+			      buff);
+		  }
+	      }
 	      break;
 	    case ALLOCA_BOUND_UNKNOWN:
 	      warning_at (loc, wcode,
diff --git a/gcc/gimple-ssa-warn-restrict.c b/gcc/gimple-ssa-warn-restrict.c
index 01503d609124..977dd860ef7a 100644
--- a/gcc/gimple-ssa-warn-restrict.c
+++ b/gcc/gimple-ssa-warn-restrict.c
@@ -1618,6 +1618,7 @@ maybe_diag_offset_bounds (location_t loc, gimple *call, tree func, int strict,
       if (DECL_P (ref.base)
 	  && TREE_CODE (type = TREE_TYPE (ref.base)) == ARRAY_TYPE)
 	{
+	  auto_diagnostic_group d;
 	  if (warning_at (loc, OPT_Warray_bounds,
 			  "%G%qD pointer overflow between offset %s "
 			  "and size %s accessing array %qD with type %qT",
@@ -1650,6 +1651,7 @@ maybe_diag_offset_bounds (location_t loc, gimple *call, tree func, int strict,
 
       if (DECL_P (ref.base))
 	{
+	  auto_diagnostic_group d;
 	  if ((ref.basesize < maxobjsize
 	       && warning_at (loc, OPT_Warray_bounds,
 			      form
diff --git a/gcc/gimplify.c b/gcc/gimplify.c
index 4a109aee27a6..e35137aec2c7 100644
--- a/gcc/gimplify.c
+++ b/gcc/gimplify.c
@@ -2173,6 +2173,7 @@ warn_implicit_fallthrough_r (gimple_stmt_iterator *gsi_p, bool *handled_ops_p,
 	  {
 	    struct label_entry *l;
 	    bool warned_p = false;
+	    auto_diagnostic_group d;
 	    if (!should_warn_for_implicit_fallthrough (gsi_p, label))
 	      /* Quiet.  */;
 	    else if (gimple_code (prev) == GIMPLE_LABEL
@@ -13079,6 +13080,7 @@ gimplify_va_arg_expr (tree *expr_p, gimple_seq *pre_p,
       /* Unfortunately, this is merely undefined, rather than a constraint
 	 violation, so we cannot make this an error.  If this call is never
 	 executed, the program is still strictly conforming.  */
+      auto_diagnostic_group d;
       warned = warning_at (xloc, 0,
 			   "%qT is promoted to %qT when passed through %<...%>",
 			   type, promoted_type);
diff --git a/gcc/hsa-gen.c b/gcc/hsa-gen.c
index 173707d8b111..6595bedac82b 100644
--- a/gcc/hsa-gen.c
+++ b/gcc/hsa-gen.c
@@ -69,6 +69,7 @@ along with GCC; see the file COPYING3.  If not see
   do \
   { \
     hsa_fail_cfun (); \
+    auto_diagnostic_group d; \
     if (warning_at (EXPR_LOCATION (hsa_cfun->m_decl), OPT_Whsa, \
 		    HSA_SORRY_MSG)) \
       inform (location, message, __VA_ARGS__); \
@@ -81,6 +82,7 @@ along with GCC; see the file COPYING3.  If not see
   do \
   { \
     hsa_fail_cfun (); \
+    auto_diagnostic_group d; \
     if (warning_at (EXPR_LOCATION (hsa_cfun->m_decl), OPT_Whsa, \
 		    HSA_SORRY_MSG)) \
       inform (location, message); \
diff --git a/gcc/ipa-devirt.c b/gcc/ipa-devirt.c
index e99d8ccd14c4..9564d651b2be 100644
--- a/gcc/ipa-devirt.c
+++ b/gcc/ipa-devirt.c
@@ -749,6 +749,7 @@ compare_virtual_tables (varpool_node *prevailing, varpool_node *vtable)
 	  prevailing = vtable;
 	  vtable = tmp;
 	}
+      auto_diagnostic_group d;
       if (warning_at (DECL_SOURCE_LOCATION
 			(TYPE_NAME (DECL_CONTEXT (vtable->decl))),
 		      OPT_Wodr,
@@ -790,22 +791,25 @@ compare_virtual_tables (varpool_node *prevailing, varpool_node *vtable)
 	             && TREE_CODE (ref1->referred->decl) == FUNCTION_DECL))
 	     && TREE_CODE (ref2->referred->decl) != FUNCTION_DECL)
 	{
-	  if (!class_type->rtti_broken
-	      && warning_at (DECL_SOURCE_LOCATION
-			      (TYPE_NAME (DECL_CONTEXT (vtable->decl))),
-			     OPT_Wodr,
-			     "virtual table of type %qD contains RTTI "
-			     "information",
-			     DECL_CONTEXT (vtable->decl)))
+	  if (!class_type->rtti_broken)
 	    {
-	      inform (DECL_SOURCE_LOCATION
-			(TYPE_NAME (DECL_CONTEXT (prevailing->decl))),
-		      "but is prevailed by one without from other translation "
-		      "unit");
-	      inform (DECL_SOURCE_LOCATION
-			(TYPE_NAME (DECL_CONTEXT (prevailing->decl))),
-		      "RTTI will not work on this type");
-	      class_type->rtti_broken = true;
+	      auto_diagnostic_group d;
+	      if (warning_at (DECL_SOURCE_LOCATION
+				  (TYPE_NAME (DECL_CONTEXT (vtable->decl))),
+				OPT_Wodr,
+				"virtual table of type %qD contains RTTI "
+				"information",
+				DECL_CONTEXT (vtable->decl)))
+		{
+		  inform (DECL_SOURCE_LOCATION
+			      (TYPE_NAME (DECL_CONTEXT (prevailing->decl))),
+			    "but is prevailed by one without from other"
+			    " translation unit");
+		  inform (DECL_SOURCE_LOCATION
+			      (TYPE_NAME (DECL_CONTEXT (prevailing->decl))),
+			    "RTTI will not work on this type");
+		  class_type->rtti_broken = true;
+		}
 	    }
 	  n2++;
           end2 = !vtable->iterate_reference (n2, ref2);
@@ -831,6 +835,7 @@ compare_virtual_tables (varpool_node *prevailing, varpool_node *vtable)
 	  if (DECL_SIZE (prevailing->decl) != DECL_SIZE (vtable->decl))
 	    {
 	      class_type->odr_violated = true;
+	      auto_diagnostic_group d;
 	      if (warning_at (DECL_SOURCE_LOCATION
 				(TYPE_NAME (DECL_CONTEXT (vtable->decl))),
 			      OPT_Wodr,
@@ -859,6 +864,7 @@ compare_virtual_tables (varpool_node *prevailing, varpool_node *vtable)
 	  if (TREE_CODE (ref1->referred->decl) != FUNCTION_DECL
 	      && TREE_CODE (ref2->referred->decl) != FUNCTION_DECL)
 	    {
+	      auto_diagnostic_group d;
 	      if (warning_at (DECL_SOURCE_LOCATION
 				(TYPE_NAME (DECL_CONTEXT (vtable->decl))),
 			      OPT_Wodr,
@@ -900,6 +906,7 @@ compare_virtual_tables (varpool_node *prevailing, varpool_node *vtable)
 	      vtable = tmp;
 	      ref1 = ref2;
 	    }
+	  auto_diagnostic_group d;
 	  if (warning_at (DECL_SOURCE_LOCATION
 			    (TYPE_NAME (DECL_CONTEXT (vtable->decl))),
 			  OPT_Wodr,
@@ -931,6 +938,7 @@ compare_virtual_tables (varpool_node *prevailing, varpool_node *vtable)
 
       /* And in the last case we have either mistmatch in between two virtual
 	 methods or two virtual table pointers.  */
+      auto_diagnostic_group d;
       if (warning_at (DECL_SOURCE_LOCATION
 			(TYPE_NAME (DECL_CONTEXT (vtable->decl))), OPT_Wodr,
 		      "virtual table of type %qD violates "
@@ -986,6 +994,7 @@ warn_odr (tree t1, tree t2, tree st1, tree st2,
   if (lto_location_cache::current_cache)
     lto_location_cache::current_cache->apply_location_cache ();
 
+  auto_diagnostic_group d;
   if (!warning_at (DECL_SOURCE_LOCATION (TYPE_NAME (t1)), OPT_Wodr,
 		   "type %qT violates the C++ One Definition Rule",
 		   t1))
diff --git a/gcc/multiple_target.c b/gcc/multiple_target.c
index a1fe09a59831..a610d9a33452 100644
--- a/gcc/multiple_target.c
+++ b/gcc/multiple_target.c
@@ -347,6 +347,7 @@ expand_target_clones (struct cgraph_node *node, bool definition)
   if (node->definition
       && !tree_versionable_function_p (node->decl))
     {
+      auto_diagnostic_group d;
       error_at (DECL_SOURCE_LOCATION (node->decl),
 		"clones for %<target_clones%> attribute cannot be created");
       const char *reason = NULL;
diff --git a/gcc/opts-common.c b/gcc/opts-common.c
index 2b5f63844fb5..91586022f7f9 100644
--- a/gcc/opts-common.c
+++ b/gcc/opts-common.c
@@ -1266,6 +1266,7 @@ cmdline_handle_error (location_t loc, const struct cl_option *option,
       unsigned int i;
       char *s;
 
+      auto_diagnostic_group d;
       if (e->unknown_error)
 	error_at (loc, e->unknown_error, arg);
       else
diff --git a/gcc/reginfo.c b/gcc/reginfo.c
index 1f36d141c73a..33befa5d350e 100644
--- a/gcc/reginfo.c
+++ b/gcc/reginfo.c
@@ -782,6 +782,7 @@ globalize_reg (tree decl, int i)
 
   if (global_regs[i])
     {
+      auto_diagnostic_group d;
       warning_at (loc, 0, 
 		  "register of %qD used for multiple global register variables",
 		  decl);
diff --git a/gcc/substring-locations.c b/gcc/substring-locations.c
index 82f2f4577f0b..1981394a3f0b 100644
--- a/gcc/substring-locations.c
+++ b/gcc/substring-locations.c
@@ -167,6 +167,7 @@ format_warning_n_va (const substring_loc &fmt_loc,
   if (substring_within_range)
     primary_label = fmt_label;
 
+  auto_diagnostic_group d;
   gcc_rich_location richloc (primary_loc, primary_label);
 
   if (param_loc != UNKNOWN_LOCATION)
diff --git a/gcc/testsuite/ChangeLog b/gcc/testsuite/ChangeLog
index 26cbc08e20ab..969e03658f9b 100644
--- a/gcc/testsuite/ChangeLog
+++ b/gcc/testsuite/ChangeLog
@@ -1,3 +1,10 @@
+2018-08-20  David Malcolm  <dmalcolm@redhat.com>
+
+	PR other/84889
+	* gcc.dg/plugin/diagnostic-group-test-1.c: New test.
+	* gcc.dg/plugin/diagnostic_group_plugin.c: New test.
+	* gcc.dg/plugin/plugin.exp (plugin_test_list): Add the new tests.
+
 2018-08-20  H.J. Lu  <hongjiu.lu@intel.com>
 
 	PR target/87014
diff --git a/gcc/testsuite/gcc.dg/plugin/diagnostic-group-test-1.c b/gcc/testsuite/gcc.dg/plugin/diagnostic-group-test-1.c
new file mode 100644
index 000000000000..962cba6941a7
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/plugin/diagnostic-group-test-1.c
@@ -0,0 +1,26 @@
+/* { dg-do compile } */
+/* { dg-options "-fdiagnostics-show-caret" } */
+
+extern void __emit_warning (const char *message);
+
+static void test_1 (void)
+{
+  __emit_warning ("warning 1");
+}
+
+/* { dg-begin-multiline-output "" }
+================================= BEGIN GROUP ==============================
+PREFIX
+   __emit_warning ("warning 1");
+   ^~~~~~~~~~~~~~~~~~~~~~~~~~~~
+PREFIX: message for note
+PREFIX:  some more detail
+PREFIX:   yet more detail
+---------------------------------- END GROUP -------------------------------
+   { dg-end-multiline-output "" } */
+
+/* { dg-begin-multiline-output "" }
+================================= BEGIN GROUP ==============================
+PREFIX: an unrelated message
+---------------------------------- END GROUP -------------------------------
+   { dg-end-multiline-output "" } */
diff --git a/gcc/testsuite/gcc.dg/plugin/diagnostic_group_plugin.c b/gcc/testsuite/gcc.dg/plugin/diagnostic_group_plugin.c
new file mode 100644
index 000000000000..3083e127d65b
--- /dev/null
+++ b/gcc/testsuite/gcc.dg/plugin/diagnostic_group_plugin.c
@@ -0,0 +1,234 @@
+/* { dg-options "-O" } */
+
+#include "gcc-plugin.h"
+#include "config.h"
+#include "system.h"
+#include "coretypes.h"
+#include "tm.h"
+#include "tree.h"
+#include "stringpool.h"
+#include "toplev.h"
+#include "basic-block.h"
+#include "hash-table.h"
+#include "vec.h"
+#include "ggc.h"
+#include "basic-block.h"
+#include "tree-ssa-alias.h"
+#include "internal-fn.h"
+#include "gimple-fold.h"
+#include "tree-eh.h"
+#include "gimple-expr.h"
+#include "is-a.h"
+#include "gimple.h"
+#include "gimple-iterator.h"
+#include "tree.h"
+#include "tree-pass.h"
+#include "intl.h"
+#include "plugin-version.h"
+#include "c-family/c-common.h"
+#include "diagnostic.h"
+#include "context.h"
+
+int plugin_is_GPL_compatible;
+
+/* A custom pass for emitting dummy warnings from the middle-end.  */
+
+const pass_data pass_data_test_groups =
+{
+  GIMPLE_PASS, /* type */
+  "test_groups", /* name */
+  OPTGROUP_NONE, /* optinfo_flags */
+  TV_NONE, /* tv_id */
+  PROP_ssa, /* properties_required */
+  0, /* properties_provided */
+  0, /* properties_destroyed */
+  0, /* todo_flags_start */
+  0, /* todo_flags_finish */
+};
+
+class pass_test_groups : public gimple_opt_pass
+{
+public:
+  pass_test_groups(gcc::context *ctxt)
+    : gimple_opt_pass(pass_data_test_groups, ctxt)
+  {}
+
+  /* opt_pass methods: */
+  bool gate (function *) { return true; }
+  virtual unsigned int execute (function *);
+
+}; // class pass_test_groups
+
+/* Determine if STMT is a call with NUM_ARGS arguments to a function
+   named FUNCNAME.
+   If so, return STMT as a gcall *.  Otherwise return NULL.  */
+
+static gcall *
+check_for_named_call (gimple *stmt,
+		      const char *funcname, unsigned int num_args)
+{
+  gcc_assert (funcname);
+
+  gcall *call = dyn_cast <gcall *> (stmt);
+  if (!call)
+    return NULL;
+
+  tree fndecl = gimple_call_fndecl (call);
+  if (!fndecl)
+    return NULL;
+
+  if (strcmp (IDENTIFIER_POINTER (DECL_NAME (fndecl)), funcname))
+    return NULL;
+
+  if (gimple_call_num_args (call) != num_args)
+    {
+      error_at (stmt->location, "expected number of args: %i (got %i)",
+		num_args, gimple_call_num_args (call));
+      return NULL;
+    }
+
+  return call;
+}
+
+/* Emit a warning at LOC.  */
+
+static void
+emit_warning (location_t loc)
+{
+  source_range src_range = get_range_from_loc (line_table, loc);
+  warning_at (loc, 0, "range %i:%i-%i:%i",
+	      LOCATION_LINE (src_range.m_start),
+	      LOCATION_COLUMN (src_range.m_start),
+	      LOCATION_LINE (src_range.m_finish),
+	      LOCATION_COLUMN (src_range.m_finish));
+}
+
+/* Code for simulating the emission of a warning from the middle-end.
+   Emit a warning for each call to a function named "__emit_warning".  */
+
+static void
+test_groups (gimple *stmt)
+{
+  gcall *call = check_for_named_call (stmt, "__emit_warning", 1);
+  if (!call)
+    return;
+
+  /* We expect an ADDR_EXPR with a STRING_CST inside it for the
+     initial arg.  */
+  tree t_addr_string = gimple_call_arg (call, 0);
+  if (TREE_CODE (t_addr_string) != ADDR_EXPR)
+    {
+      error_at (call->location, "string literal required for arg 1");
+      return;
+    }
+
+  tree t_string = TREE_OPERAND (t_addr_string, 0);
+  if (TREE_CODE (t_string) != STRING_CST)
+    {
+      error_at (call->location, "string literal required for arg 1");
+      return;
+    }
+
+  {
+    auto_diagnostic_group d;
+    if (warning_at (call->location, 0, "%s", call,
+		    TREE_STRING_POINTER (t_string)))
+      {
+	inform (call->location, "message for note");
+	inform (call->location, " some more detail");
+	inform (call->location, "  yet more detail");
+      }
+  }
+  inform (call->location, "an unrelated message");
+}
+
+/* Call test_groups on every statement within FUN.  */
+
+unsigned int
+pass_test_groups::execute (function *fun)
+{
+  gimple_stmt_iterator gsi;
+  basic_block bb;
+
+  FOR_EACH_BB_FN (bb, fun)
+    for (gsi = gsi_start_bb (bb); !gsi_end_p (gsi); gsi_next (&gsi))
+      {
+	gimple *stmt = gsi_stmt (gsi);
+	test_groups (stmt);
+      }
+
+  return 0;
+}
+
+/* Custom diagnostic callback, to avoid having the path in the
+   expected output.  */
+
+void
+test_diagnostic_starter (diagnostic_context *context,
+			 diagnostic_info *diagnostic)
+{
+  pp_set_prefix (context->printer, xstrdup ("PREFIX: "));
+}
+
+/* Custom diagnostic callback, to avoid having the path in the
+   expected output.  */
+
+void
+test_diagnostic_start_span_fn (diagnostic_context *context,
+			       expanded_location exploc)
+{
+  pp_string (context->printer, "START_SPAN_FN: ");
+  pp_newline (context->printer);
+}
+
+/* Custom diagnostic callback: loudly announce a new diagnostic group.  */
+
+static void
+test_begin_group_cb (diagnostic_context * context)
+{
+  pp_string (context->printer,
+	     "================================= BEGIN GROUP ==============================");
+  pp_newline (context->printer);
+}
+
+/* Custom diagnostic callback: loudly announce the end of a
+   diagnostic group.  */
+
+static void
+test_end_group_cb (diagnostic_context * context)
+{
+  pp_string (context->printer,
+	     "---------------------------------- END GROUP -------------------------------");
+  pp_newline_and_flush (context->printer);
+}
+
+/* Entrypoint for the plugin.
+   Install custom callbacks into the global_dc.
+   Create and register the custom pass.  */
+
+int
+plugin_init (struct plugin_name_args *plugin_info,
+	     struct plugin_gcc_version *version)
+{
+  struct register_pass_info pass_info;
+  const char *plugin_name = plugin_info->base_name;
+  int argc = plugin_info->argc;
+  struct plugin_argument *argv = plugin_info->argv;
+
+  if (!plugin_default_version_check (version, &gcc_version))
+    return 1;
+
+  diagnostic_starter (global_dc) = test_diagnostic_starter;
+  global_dc->start_span = test_diagnostic_start_span_fn;
+  global_dc->begin_group_cb = test_begin_group_cb;
+  global_dc->end_group_cb = test_end_group_cb;
+
+  pass_info.pass = new pass_test_groups (g);
+  pass_info.reference_pass_name = "*warn_function_noreturn";
+  pass_info.ref_pass_instance_number = 1;
+  pass_info.pos_op = PASS_POS_INSERT_AFTER;
+  register_callback (plugin_name, PLUGIN_PASS_MANAGER_SETUP, NULL,
+		     &pass_info);
+
+  return 0;
+}
diff --git a/gcc/testsuite/gcc.dg/plugin/plugin.exp b/gcc/testsuite/gcc.dg/plugin/plugin.exp
index 86ab1dd8d932..46246a2449ec 100644
--- a/gcc/testsuite/gcc.dg/plugin/plugin.exp
+++ b/gcc/testsuite/gcc.dg/plugin/plugin.exp
@@ -69,6 +69,8 @@ set plugin_test_list [list \
     { poly-int-05_plugin.c poly-int-test-1.c } \
     { poly-int-06_plugin.c poly-int-test-1.c } \
     { poly-int-07_plugin.c poly-int-test-1.c } \
+    { diagnostic_group_plugin.c \
+	  diagnostic-group-test-1.c } \
     { diagnostic_plugin_test_show_locus.c \
 	  diagnostic-test-show-locus-bw.c \
 	  diagnostic-test-show-locus-color.c \
diff --git a/gcc/tree-inline.c b/gcc/tree-inline.c
index 21464d6e28fb..2b6bb5c0e313 100644
--- a/gcc/tree-inline.c
+++ b/gcc/tree-inline.c
@@ -4427,6 +4427,7 @@ expand_call_inline (basic_block bb, gimple *stmt, copy_body_data *id)
 	       /* Avoid warnings during early inline pass. */
 	       && symtab->global_info_ready)
 	{
+	  auto_diagnostic_group d;
 	  if (warning (OPT_Winline, "inlining failed in call to %q+F: %s",
 		       fn, _(cgraph_inline_failed_string (reason))))
 	    {
diff --git a/gcc/tree-ssa-ccp.c b/gcc/tree-ssa-ccp.c
index 63c95318aced..d0f799eb39de 100644
--- a/gcc/tree-ssa-ccp.c
+++ b/gcc/tree-ssa-ccp.c
@@ -3454,6 +3454,7 @@ pass_post_ipa_warn::execute (function *fun)
 			continue;
 
 		      location_t loc = gimple_location (stmt);
+		      auto_diagnostic_group d;
 		      if (warning_at (loc, OPT_Wnonnull,
 				      "%Gargument %u null where non-null "
 				      "expected", stmt, i + 1))
diff --git a/gcc/tree-ssa-loop-niter.c b/gcc/tree-ssa-loop-niter.c
index fbdf838496bc..7b6c91ca6daf 100644
--- a/gcc/tree-ssa-loop-niter.c
+++ b/gcc/tree-ssa-loop-niter.c
@@ -3231,6 +3231,7 @@ do_warn_aggressive_loop_optimizations (struct loop *loop,
   char buf[WIDE_INT_PRINT_BUFFER_SIZE];
   print_dec (i_bound, buf, TYPE_UNSIGNED (TREE_TYPE (loop->nb_iterations))
 	     ? UNSIGNED : SIGNED);
+  auto_diagnostic_group d;
   if (warning_at (gimple_location (stmt), OPT_Waggressive_loop_optimizations,
 		  "iteration %s invokes undefined behavior", buf))
     inform (gimple_location (estmt), "within this loop");
diff --git a/gcc/tree-ssa-uninit.c b/gcc/tree-ssa-uninit.c
index 8ccbc85970a4..a93610084f2a 100644
--- a/gcc/tree-ssa-uninit.c
+++ b/gcc/tree-ssa-uninit.c
@@ -178,6 +178,7 @@ warn_uninit (enum opt_code wc, tree t, tree expr, tree var,
   cfun_loc = DECL_SOURCE_LOCATION (cfun->decl);
   xloc = expand_location (location);
   floc = expand_location (cfun_loc);
+  auto_diagnostic_group d;
   if (warning_at (location, wc, gmsgid, expr))
     {
       TREE_NO_WARNING (expr) = 1;
diff --git a/gcc/tree.c b/gcc/tree.c
index 0ec74af0c1c7..dd3439f60c96 100644
--- a/gcc/tree.c
+++ b/gcc/tree.c
@@ -12613,6 +12613,7 @@ warn_deprecated_use (tree node, tree attr)
   bool w = false;
   if (DECL_P (node))
     {
+      auto_diagnostic_group d;
       if (msg)
 	w = warning (OPT_Wdeprecated_declarations,
 		     "%qD is deprecated: %s", node, (const char *) msg);
@@ -12636,6 +12637,7 @@ warn_deprecated_use (tree node, tree attr)
 	    what = DECL_NAME (TYPE_NAME (node));
 	}
 
+      auto_diagnostic_group d;
       if (what)
 	{
 	  if (msg)
-- 
GitLab