diff --git a/gcc/diagnostic-buffer.h b/gcc/diagnostic-buffer.h new file mode 100644 index 0000000000000000000000000000000000000000..07acd04492099696ba2d99908fdc0d3066ee754f --- /dev/null +++ b/gcc/diagnostic-buffer.h @@ -0,0 +1,109 @@ +/* Support for buffering diagnostics before flushing them to output format. + Copyright (C) 2024 Free Software Foundation, Inc. + Contributed by David Malcolm <dmalcolm@redhat.com>. + +This file is part of GCC. + +GCC is free software; you can redistribute it and/or modify it under +the terms of the GNU General Public License as published by the Free +Software Foundation; either version 3, or (at your option) any later +version. + +GCC is distributed in the hope that it will be useful, but WITHOUT ANY +WARRANTY; without even the implied warranty of MERCHANTABILITY or +FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License +for more details. + +You should have received a copy of the GNU General Public License +along with GCC; see the file COPYING3. If not see +<http://www.gnu.org/licenses/>. */ + +#ifndef GCC_DIAGNOSTIC_BUFFER_H +#define GCC_DIAGNOSTIC_BUFFER_H + +#include "diagnostic.h" + +class diagnostic_per_format_buffer; +class diagnostic_output_format; + class diagnostic_text_output_format; + +/* Class representing a buffer of zero or more diagnostics that + have been reported to a diagnostic_context, but which haven't + yet been flushed. + + A diagnostic_buffer can be: + + * flushed to the diagnostic_context, which issues + the diagnostics within the buffer to the output format + and checks for limits such as -fmax-errors=, or + + * moved to another diagnostic_buffer, which moves the diagnostics + within the first buffer to the other buffer, appending them after any + existing diagnostics within the destination buffer, emptying the + source buffer, or + + * cleared, which discards any diagnostics within the buffer + without issuing them to the output format. + + Since a buffer needs to contain output-format-specific data, + it's not possible to change the output format of the + diagnostic_context once any buffers are non-empty. + + To simplify implementing output formats, it's not possible + to change buffering on a diagnostic_context whilst within a + diagnostic group. */ + +class diagnostic_buffer +{ + public: + friend class diagnostic_context; + + diagnostic_buffer (diagnostic_context &ctxt); + ~diagnostic_buffer (); + + void dump (FILE *out, int indent) const; + void DEBUG_FUNCTION dump () const { dump (stderr, 0); } + + int diagnostic_count (diagnostic_t kind) const + { + return m_diagnostic_counters.get_count (kind); + } + + bool empty_p () const; + + void move_to (diagnostic_buffer &dest); + + private: + void ensure_per_format_buffer (); + + diagnostic_context &m_ctxt; + diagnostic_per_format_buffer *m_per_format_buffer; + + /* The number of buffered diagnostics of each kind. */ + diagnostic_counters m_diagnostic_counters; +}; + +/* Implementation detail of diagnostic_buffer. + + Abstract base class describing how to represent zero of more + buffered diagnostics for a particular diagnostic_output_format + (e.g. text vs SARIF). + + Each diagnostic_output_format subclass should implement its own + subclass for handling diagnostic_buffer. */ + +class diagnostic_per_format_buffer +{ +public: + virtual ~diagnostic_per_format_buffer () {} + + virtual void dump (FILE *out, int indent) const = 0; + void DEBUG_FUNCTION dump () const { dump (stderr, 0); } + + virtual bool empty_p () const = 0; + virtual void move_to (diagnostic_per_format_buffer &dest) = 0; + virtual void clear () = 0; + virtual void flush () = 0; +}; + +#endif /* ! GCC_DIAGNOSTIC_BUFFER_H */ diff --git a/gcc/diagnostic-format-json.cc b/gcc/diagnostic-format-json.cc index 4f035dd2fae33118a87320257e2e792a8475c152..022e3a9ae7d3a8f2647aed8312272a2527e28fe7 100644 --- a/gcc/diagnostic-format-json.cc +++ b/gcc/diagnostic-format-json.cc @@ -21,6 +21,7 @@ along with GCC; see the file COPYING3. If not see #include "config.h" #define INCLUDE_MEMORY +#define INCLUDE_VECTOR #include "system.h" #include "coretypes.h" #include "diagnostic.h" @@ -28,22 +29,60 @@ along with GCC; see the file COPYING3. If not see #include "diagnostic-metadata.h" #include "diagnostic-path.h" #include "diagnostic-format.h" +#include "diagnostic-buffer.h" #include "json.h" #include "selftest.h" #include "logical-location.h" #include "make-unique.h" +class json_output_format; + +/* Concrete buffering implementation subclass for JSON output. */ + +class diagnostic_json_format_buffer : public diagnostic_per_format_buffer +{ +public: + friend class json_output_format; + + diagnostic_json_format_buffer (json_output_format &format) + : m_format (format) + {} + + void dump (FILE *out, int indent) const final override; + bool empty_p () const final override; + void move_to (diagnostic_per_format_buffer &dest) final override; + void clear () final override; + void flush () final override; + +private: + json_output_format &m_format; + std::vector<std::unique_ptr<json::object>> m_results; +}; + /* Subclass of diagnostic_output_format for JSON output. */ class json_output_format : public diagnostic_output_format { public: + friend class diagnostic_json_format_buffer; + void dump (FILE *out, int indent) const override { fprintf (out, "%*sjson_output_format\n", indent, ""); diagnostic_output_format::dump (out, indent); } + diagnostic_per_format_buffer *make_per_format_buffer () final override + { + return new diagnostic_json_format_buffer (*this); + } + void set_buffer (diagnostic_per_format_buffer *base_buffer) final override + { + diagnostic_json_format_buffer *buffer + = static_cast<diagnostic_json_format_buffer *> (base_buffer); + m_buffer = buffer; + } + void on_begin_group () final override { /* No-op. */ @@ -69,6 +108,7 @@ protected: json_output_format (diagnostic_context &context, bool formatted) : diagnostic_output_format (context), + m_buffer (nullptr), m_toplevel_array (::make_unique<json::array> ()), m_cur_group (nullptr), m_cur_children_array (nullptr), @@ -86,6 +126,8 @@ protected: } private: + diagnostic_json_format_buffer *m_buffer; + /* The top-level JSON array of pending diagnostics. */ std::unique_ptr<json::array> m_toplevel_array; @@ -231,6 +273,51 @@ make_json_for_path (diagnostic_context &context, return path_array; } +/* class diagnostic_json_format_buffer : public diagnostic_per_format_buffer. */ + +void +diagnostic_json_format_buffer::dump (FILE *out, int indent) const +{ + fprintf (out, "%*sdiagnostic_json_format_buffer:\n", indent, ""); + int idx = 0; + for (auto &result : m_results) + { + fprintf (out, "%*sresult[%i]:\n", indent + 2, "", idx); + result->dump (out, true); + fprintf (out, "\n"); + ++idx; + } +} + +bool +diagnostic_json_format_buffer::empty_p () const +{ + return m_results.empty (); +} + +void +diagnostic_json_format_buffer::move_to (diagnostic_per_format_buffer &base) +{ + diagnostic_json_format_buffer &dest + = static_cast<diagnostic_json_format_buffer &> (base); + for (auto &&result : m_results) + dest.m_results.push_back (std::move (result)); + m_results.clear (); +} + +void +diagnostic_json_format_buffer::clear () +{ + m_results.clear (); +} + +void +diagnostic_json_format_buffer::flush () +{ + for (auto &&result : m_results) + m_format.m_toplevel_array->append (std::move (result)); + m_results.clear (); +} /* Implementation of "on_report_diagnostic" vfunc for JSON output. Generate a JSON object for DIAGNOSTIC, and store for output @@ -277,24 +364,32 @@ json_output_format::on_report_diagnostic (const diagnostic_info &diagnostic, free (option_url); } - /* If we've already emitted a diagnostic within this auto_diagnostic_group, - then add diag_obj to its "children" array. */ - if (m_cur_group) + if (m_buffer) { - gcc_assert (m_cur_children_array); - m_cur_children_array->append (diag_obj); + gcc_assert (!m_cur_group); + m_buffer->m_results.push_back (std::unique_ptr<json::object> (diag_obj)); } else { - /* Otherwise, make diag_obj be the top-level object within the group; - add a "children" array and record the column origin. */ - m_cur_group = diag_obj; - std::unique_ptr<json::array> children_array - = ::make_unique<json::array> (); - m_cur_children_array = children_array.get (); // borrowed - diag_obj->set ("children", std::move (children_array)); - diag_obj->set_integer ("column-origin", m_context.m_column_origin); - m_toplevel_array->append (diag_obj); + /* If we've already emitted a diagnostic within this auto_diagnostic_group, + then add diag_obj to its "children" array. */ + if (m_cur_group) + { + gcc_assert (m_cur_children_array); + m_cur_children_array->append (diag_obj); + } + else + { + /* Otherwise, make diag_obj be the top-level object within the group; + add a "children" array and record the column origin. */ + m_cur_group = diag_obj; + std::unique_ptr<json::array> children_array + = ::make_unique<json::array> (); + m_cur_children_array = children_array.get (); // borrowed + diag_obj->set ("children", std::move (children_array)); + diag_obj->set_integer ("column-origin", m_context.m_column_origin); + m_toplevel_array->append (diag_obj); + } } /* diag_obj is now owned by either m_cur_children_array or diff --git a/gcc/diagnostic-format-sarif.cc b/gcc/diagnostic-format-sarif.cc index f64c83ad6e1469465129adb8fcca3584a9fb4e5b..4ce3561900077f5ba66f60d5a3c60bb41337c1bd 100644 --- a/gcc/diagnostic-format-sarif.cc +++ b/gcc/diagnostic-format-sarif.cc @@ -30,6 +30,7 @@ along with GCC; see the file COPYING3. If not see #include "diagnostic-metadata.h" #include "diagnostic-path.h" #include "diagnostic-format.h" +#include "diagnostic-buffer.h" #include "json.h" #include "cpplib.h" #include "logical-location.h" @@ -603,6 +604,36 @@ public: render (const sarif_builder &builder) const = 0; }; +/* Concrete buffering implementation subclass for JSON output. */ + +class diagnostic_sarif_format_buffer : public diagnostic_per_format_buffer +{ +public: + friend class sarif_output_format; + + diagnostic_sarif_format_buffer (sarif_builder &builder) + : m_builder (builder) + {} + + void dump (FILE *out, int indent) const final override; + bool empty_p () const final override; + void move_to (diagnostic_per_format_buffer &dest) final override; + void clear () final override; + void flush () final override; + + void add_result (std::unique_ptr<sarif_result> result) + { + m_results.push_back (std::move (result)); + } + + size_t num_results () const { return m_results.size (); } + sarif_result &get_result (size_t idx) { return *m_results[idx]; } + +private: + sarif_builder &m_builder; + std::vector<std::unique_ptr<sarif_result>> m_results; +}; + /* A class for managing SARIF output (for -fdiagnostics-format=sarif-stderr and -fdiagnostics-format=sarif-file). @@ -646,6 +677,8 @@ public: class sarif_builder { public: + friend class diagnostic_sarif_format_buffer; + sarif_builder (diagnostic_context &context, const line_maps *line_maps, const char *main_input_filename_, @@ -654,7 +687,8 @@ public: ~sarif_builder (); void on_report_diagnostic (const diagnostic_info &diagnostic, - diagnostic_t orig_diag_kind); + diagnostic_t orig_diag_kind, + diagnostic_sarif_format_buffer *buffer); void emit_diagram (const diagnostic_diagram &diagram); void end_group (); @@ -700,6 +734,14 @@ public: token_printer &get_token_printer () { return m_token_printer; } enum sarif_version get_version () const { return m_version; } + size_t num_results () const { return m_results_array->size (); } + sarif_result &get_result (size_t idx) + { + auto element = (*m_results_array)[idx]; + gcc_assert (element); + return *static_cast<sarif_result *> (element); + } + private: class sarif_token_printer : public token_printer { @@ -1673,7 +1715,8 @@ sarif_builder::make_stack_from_backtrace () void sarif_builder::on_report_diagnostic (const diagnostic_info &diagnostic, - diagnostic_t orig_diag_kind) + diagnostic_t orig_diag_kind, + diagnostic_sarif_format_buffer *buffer) { pp_output_formatted_text (m_printer, m_context.get_urlifier ()); @@ -1693,6 +1736,15 @@ sarif_builder::on_report_diagnostic (const diagnostic_info &diagnostic, return; } + if (buffer) + { + /* When buffering, we can only handle top-level results. */ + gcc_assert (!m_cur_group_result); + buffer->add_result (make_result_object (diagnostic, orig_diag_kind, + m_next_result_idx++)); + return; + } + if (m_cur_group_result) /* Nested diagnostic. */ m_cur_group_result->on_nested_diagnostic (diagnostic, @@ -3289,6 +3341,55 @@ sarif_builder::make_artifact_content_object (const char *text) const return content_obj; } +/* class diagnostic_sarif_format_buffer : public diagnostic_per_format_buffer. */ + +void +diagnostic_sarif_format_buffer::dump (FILE *out, int indent) const +{ + fprintf (out, "%*sdiagnostic_sarif_format_buffer:\n", indent, ""); + int idx = 0; + for (auto &result : m_results) + { + fprintf (out, "%*sresult[%i]:\n", indent + 2, "", idx); + result->dump (out, true); + fprintf (out, "\n"); + ++idx; + } +} + +bool +diagnostic_sarif_format_buffer::empty_p () const +{ + return m_results.empty (); +} + +void +diagnostic_sarif_format_buffer::move_to (diagnostic_per_format_buffer &base) +{ + diagnostic_sarif_format_buffer &dest + = static_cast<diagnostic_sarif_format_buffer &> (base); + for (auto &&result : m_results) + dest.m_results.push_back (std::move (result)); + m_results.clear (); +} + +void +diagnostic_sarif_format_buffer::clear () +{ + m_results.clear (); +} + +void +diagnostic_sarif_format_buffer::flush () +{ + for (auto &&result : m_results) + { + result->process_worklist (m_builder); + m_builder.m_results_array->append<sarif_result> (std::move (result)); + } + m_results.clear (); +} + class sarif_output_format : public diagnostic_output_format { public: @@ -3308,6 +3409,17 @@ public: diagnostic_output_format::dump (out, indent); } + diagnostic_per_format_buffer *make_per_format_buffer () final override + { + return new diagnostic_sarif_format_buffer (m_builder); + } + void set_buffer (diagnostic_per_format_buffer *base_buffer) final override + { + diagnostic_sarif_format_buffer *buffer + = static_cast<diagnostic_sarif_format_buffer *> (base_buffer); + m_buffer = buffer; + } + void on_begin_group () final override { /* No-op, */ @@ -3320,7 +3432,7 @@ public: on_report_diagnostic (const diagnostic_info &diagnostic, diagnostic_t orig_diag_kind) final override { - m_builder.on_report_diagnostic (diagnostic, orig_diag_kind); + m_builder.on_report_diagnostic (diagnostic, orig_diag_kind, m_buffer); } void on_diagram (const diagnostic_diagram &diagram) final override { @@ -3333,6 +3445,9 @@ public: sarif_builder &get_builder () { return m_builder; } + size_t num_results () const { return m_builder.num_results (); } + sarif_result &get_result (size_t idx) { return m_builder.get_result (idx); } + protected: sarif_output_format (diagnostic_context &context, const line_maps *line_maps, @@ -3340,10 +3455,12 @@ protected: bool formatted, enum sarif_version version) : diagnostic_output_format (context), - m_builder (context, line_maps, main_input_filename_, formatted, version) + m_builder (context, line_maps, main_input_filename_, formatted, version), + m_buffer (nullptr) {} sarif_builder m_builder; + diagnostic_sarif_format_buffer *m_buffer; }; class sarif_stream_output_format : public sarif_output_format @@ -3658,6 +3775,9 @@ public: return m_format->flush_to_object (); } + size_t num_results () const { return m_format->num_results (); } + sarif_result &get_result (size_t idx) { return m_format->get_result (idx); } + private: class buffered_output_format : public sarif_output_format { @@ -4047,6 +4167,15 @@ get_result_from_log (const sarif_log *log) return expect_json_object (SELFTEST_LOCATION, result); } +static const json::object * +get_message_from_result (const sarif_result &result) +{ + // 3.27.11: + auto message_obj + = EXPECT_JSON_OBJECT_WITH_OBJECT_PROPERTY (&result, "message"); + return message_obj; +} + /* Assuming that a single diagnostic has been emitted to DC, get a json::object for the messsage object within the result. */ @@ -4139,6 +4268,93 @@ test_message_with_embedded_link (enum sarif_version version) } } +static void +test_buffering (enum sarif_version version) +{ + test_sarif_diagnostic_context dc ("test.c", version); + + diagnostic_buffer buf_a (dc); + diagnostic_buffer buf_b (dc); + + rich_location rich_loc (line_table, UNKNOWN_LOCATION); + + ASSERT_EQ (dc.diagnostic_count (DK_ERROR), 0); + ASSERT_EQ (buf_a.diagnostic_count (DK_ERROR), 0); + ASSERT_EQ (buf_b.diagnostic_count (DK_ERROR), 0); + ASSERT_EQ (dc.num_results (), 0); + ASSERT_TRUE (buf_a.empty_p ()); + ASSERT_TRUE (buf_b.empty_p ()); + + /* Unbuffered diagnostic. */ + { + dc.report (DK_ERROR, rich_loc, nullptr, 0, + "message 1"); + + ASSERT_EQ (dc.diagnostic_count (DK_ERROR), 1); + ASSERT_EQ (buf_a.diagnostic_count (DK_ERROR), 0); + ASSERT_EQ (buf_b.diagnostic_count (DK_ERROR), 0); + ASSERT_EQ (dc.num_results (), 1); + sarif_result &result_obj = dc.get_result (0); + auto message_obj = get_message_from_result (result_obj); + ASSERT_JSON_STRING_PROPERTY_EQ (message_obj, "text", + "message 1"); + ASSERT_TRUE (buf_a.empty_p ()); + ASSERT_TRUE (buf_b.empty_p ()); + } + + /* Buffer diagnostic into buffer A. */ + { + dc.set_diagnostic_buffer (&buf_a); + dc.report (DK_ERROR, rich_loc, nullptr, 0, + "message in buffer a"); + ASSERT_EQ (dc.diagnostic_count (DK_ERROR), 1); + ASSERT_EQ (buf_a.diagnostic_count (DK_ERROR), 1); + ASSERT_EQ (buf_b.diagnostic_count (DK_ERROR), 0); + ASSERT_EQ (dc.num_results (), 1); + ASSERT_FALSE (buf_a.empty_p ()); + ASSERT_TRUE (buf_b.empty_p ()); + } + + /* Buffer diagnostic into buffer B. */ + { + dc.set_diagnostic_buffer (&buf_b); + dc.report (DK_ERROR, rich_loc, nullptr, 0, + "message in buffer b"); + ASSERT_EQ (dc.diagnostic_count (DK_ERROR), 1); + ASSERT_EQ (buf_a.diagnostic_count (DK_ERROR), 1); + ASSERT_EQ (buf_b.diagnostic_count (DK_ERROR), 1); + ASSERT_EQ (dc.num_results (), 1); + ASSERT_FALSE (buf_a.empty_p ()); + ASSERT_FALSE (buf_b.empty_p ()); + } + + /* Flush buffer B to dc. */ + { + dc.flush_diagnostic_buffer (buf_b); + ASSERT_EQ (dc.diagnostic_count (DK_ERROR), 2); + ASSERT_EQ (buf_a.diagnostic_count (DK_ERROR), 1); + ASSERT_EQ (buf_b.diagnostic_count (DK_ERROR), 0); + ASSERT_EQ (dc.num_results (), 2); + sarif_result &result_1_obj = dc.get_result (1); + auto message_1_obj = get_message_from_result (result_1_obj); + ASSERT_JSON_STRING_PROPERTY_EQ (message_1_obj, "text", + "message in buffer b"); + ASSERT_FALSE (buf_a.empty_p ()); + ASSERT_TRUE (buf_b.empty_p ()); + } + + /* Clear buffer A. */ + { + dc.clear_diagnostic_buffer (buf_a); + ASSERT_EQ (dc.diagnostic_count (DK_ERROR), 2); + ASSERT_EQ (buf_a.diagnostic_count (DK_ERROR), 0); + ASSERT_EQ (buf_b.diagnostic_count (DK_ERROR), 0); + ASSERT_EQ (dc.num_results (), 2); + ASSERT_TRUE (buf_a.empty_p ()); + ASSERT_TRUE (buf_b.empty_p ()); + } +} + static void run_tests_per_version (const line_table_case &case_) { @@ -4168,6 +4384,7 @@ diagnostic_format_sarif_cc_tests () test_simple_log (version); test_message_with_embedded_link (version); + test_buffering (version); } /* Run tests per (line-table-case, SARIF version) pair. */ diff --git a/gcc/diagnostic-format-text.cc b/gcc/diagnostic-format-text.cc index f6ec88155c7fce3da31f1eb170ccc1632cf39854..03f5518d620660747d77b043ccacde6e8a7b87c2 100644 --- a/gcc/diagnostic-format-text.cc +++ b/gcc/diagnostic-format-text.cc @@ -32,6 +32,7 @@ along with GCC; see the file COPYING3. If not see #include "diagnostic-client-data-hooks.h" #include "diagnostic-diagram.h" #include "diagnostic-format-text.h" +#include "diagnostic-buffer.h" #include "text-art/theme.h" /* Disable warnings about quoting issues in the pp_xxx calls below @@ -41,6 +42,90 @@ along with GCC; see the file COPYING3. If not see # pragma GCC diagnostic ignored "-Wformat-diag" #endif +/* Concrete buffering implementation subclass for JSON output. */ + +class diagnostic_text_format_buffer : public diagnostic_per_format_buffer +{ +public: + friend class diagnostic_text_output_format; + + diagnostic_text_format_buffer (diagnostic_output_format &format); + + void dump (FILE *out, int indent) const final override; + + bool empty_p () const final override; + void move_to (diagnostic_per_format_buffer &dest) final override; + void clear () final override; + void flush () final override; + +private: + diagnostic_output_format &m_format; + output_buffer m_output_buffer; +}; + +/* class diagnostic_text_format_buffer : public diagnostic_per_format_buffer. */ + +diagnostic_text_format_buffer:: +diagnostic_text_format_buffer (diagnostic_output_format &format) +: m_format (format) +{ + m_output_buffer.m_flush_p = false; +} + +void +diagnostic_text_format_buffer::dump (FILE *out, int indent) const +{ + fprintf (out, "%*sdiagnostic_text_format_buffer:\n", indent, ""); + m_output_buffer.dump (out, indent + 2); +} + +bool +diagnostic_text_format_buffer::empty_p () const +{ + return output_buffer_last_position_in_text (&m_output_buffer) == nullptr; +} + +void +diagnostic_text_format_buffer::move_to (diagnostic_per_format_buffer &base_dest) +{ + diagnostic_text_format_buffer &dest + = static_cast<diagnostic_text_format_buffer &> (base_dest); + const char *str = output_buffer_formatted_text (&m_output_buffer); + output_buffer_append_r (&dest.m_output_buffer, str, strlen (str)); + + obstack_free (m_output_buffer.m_obstack, + obstack_base (m_output_buffer.m_obstack)); + m_output_buffer.m_line_length = 0; +} + +void +diagnostic_text_format_buffer::clear () +{ + pretty_printer *const pp = m_format.get_printer (); + output_buffer *const old_output_buffer = pp_buffer (pp); + + pp_buffer (pp) = &m_output_buffer; + + pp_clear_output_area (pp); + gcc_assert (empty_p ()); + + pp_buffer (pp) = old_output_buffer; +} + +void +diagnostic_text_format_buffer::flush () +{ + pretty_printer *const pp = m_format.get_printer (); + output_buffer *const old_output_buffer = pp_buffer (pp); + + pp_buffer (pp) = &m_output_buffer; + + pp_really_flush (pp); + gcc_assert (empty_p ()); + + pp_buffer (pp) = old_output_buffer; +} + /* class diagnostic_text_output_format : public diagnostic_output_format. */ diagnostic_text_output_format::~diagnostic_text_output_format () @@ -74,6 +159,37 @@ diagnostic_text_output_format::dump (FILE *out, int indent) const { fprintf (out, "%*sdiagnostic_text_output_format\n", indent, ""); diagnostic_output_format::dump (out, indent); + fprintf (out, "%*ssaved_output_buffer:\n", indent + 2, ""); + if (m_saved_output_buffer) + m_saved_output_buffer->dump (out, indent + 4); + else + fprintf (out, "%*s(none):\n", indent + 4, ""); +} + +void +diagnostic_text_output_format::set_buffer (diagnostic_per_format_buffer *base) +{ + diagnostic_text_format_buffer * const buffer + = static_cast<diagnostic_text_format_buffer *> (base); + + pretty_printer *const pp = get_printer (); + + if (!m_saved_output_buffer) + m_saved_output_buffer = pp_buffer (pp); + + if (buffer) + pp_buffer (pp) = &buffer->m_output_buffer; + else + { + gcc_assert (m_saved_output_buffer); + pp_buffer (pp) = m_saved_output_buffer; + } +} + +diagnostic_per_format_buffer * +diagnostic_text_output_format::make_per_format_buffer () +{ + return new diagnostic_text_format_buffer (*this); } /* Implementation of diagnostic_output_format::on_report_diagnostic vfunc diff --git a/gcc/diagnostic-format-text.h b/gcc/diagnostic-format-text.h index d3b10dd518aeb688e4dd6b630e9b52a20cf6d494..12a65bf6ee8f6176db25a45ae0f8a621cf3ca8a5 100644 --- a/gcc/diagnostic-format-text.h +++ b/gcc/diagnostic-format-text.h @@ -34,6 +34,7 @@ class diagnostic_text_output_format : public diagnostic_output_format public: diagnostic_text_output_format (diagnostic_context &context) : diagnostic_output_format (context), + m_saved_output_buffer (nullptr), m_column_policy (context), m_last_module (nullptr), m_includes_seen (nullptr) @@ -42,6 +43,9 @@ public: void dump (FILE *out, int indent) const override; + diagnostic_per_format_buffer *make_per_format_buffer () final override; + void set_buffer (diagnostic_per_format_buffer *) final override; + void on_begin_group () override {} void on_end_group () override {} void on_report_diagnostic (const diagnostic_info &, @@ -81,6 +85,9 @@ private: label_text get_location_text (const expanded_location &s) const; bool includes_seen_p (const line_map_ordinary *map); + /* For handling diagnostic_buffer. */ + output_buffer *m_saved_output_buffer; + diagnostic_column_policy m_column_policy; /* Used to detect when the input file stack has changed since last diff --git a/gcc/diagnostic-format.h b/gcc/diagnostic-format.h index e514c6f1ced885a7c09913a3849e2a30a09e9f34..e2ae155eec1ec02ec7e7182bdf5aa4e1ccf37776 100644 --- a/gcc/diagnostic-format.h +++ b/gcc/diagnostic-format.h @@ -23,6 +23,8 @@ along with GCC; see the file COPYING3. If not see #include "diagnostic.h" +class diagnostic_per_format_buffer; + /* Abstract base class for a particular output format for diagnostics; each value of -fdiagnostics-output-format= will have its own implementation. */ @@ -34,6 +36,16 @@ public: virtual void dump (FILE *out, int indent) const; + /* Vfunc for making an appropriate diagnostic_per_format_buffer + subclass for this format. */ + virtual diagnostic_per_format_buffer *make_per_format_buffer () = 0; + + /* Vfunc to be called when call a diagnostic_buffer is set on + a diagnostic_context, to update this format. The per_format_buffer + will be one created by make_per_format_buffer above and thus be + of the correct subclass. */ + virtual void set_buffer (diagnostic_per_format_buffer *) = 0; + virtual void on_begin_group () = 0; virtual void on_end_group () = 0; diff --git a/gcc/diagnostic.cc b/gcc/diagnostic.cc index a9ef1438031c49a4086fadfbab1b0ed12ea50416..f1cfb3a16867cba8bd1548bc155b6693bfaa295b 100644 --- a/gcc/diagnostic.cc +++ b/gcc/diagnostic.cc @@ -49,6 +49,7 @@ along with GCC; see the file COPYING3. If not see #include "text-art/theme.h" #include "pretty-print-urlifier.h" #include "logical-location.h" +#include "diagnostic-buffer.h" #ifdef HAVE_TERMIOS_H # include <termios.h> @@ -226,7 +227,7 @@ diagnostic_context::initialize (int n_opts) new (m_printer) pretty_printer (); m_file_cache = new file_cache (); - memset (m_diagnostic_count, 0, sizeof m_diagnostic_count); + m_diagnostic_counters.clear (); m_warning_as_error_requested = false; m_n_opts = n_opts; m_option_classifier.init (n_opts); @@ -287,6 +288,7 @@ diagnostic_context::initialize (int n_opts) m_client_data_hooks = nullptr; m_diagrams.m_theme = nullptr; m_original_argv = nullptr; + m_diagnostic_buffer = nullptr; enum diagnostic_text_art_charset text_art_charset = DIAGNOSTICS_TEXT_ART_CHARSET_EMOJI; @@ -377,6 +379,8 @@ diagnostic_context::finish () while (m_diagnostic_groups.m_nesting_depth > 0) end_group (); + set_diagnostic_buffer (nullptr); + /* Clean ups. */ delete m_output_format; @@ -424,16 +428,16 @@ void diagnostic_context::dump (FILE *out) const { fprintf (out, "diagnostic_context:\n"); - fprintf (out, " counts:\n"); - for (int i = 0; i < DK_LAST_DIAGNOSTIC_KIND; i++) - if (m_diagnostic_count[i] > 0) - fprintf (out, " %s%i\n", - get_diagnostic_kind_text (static_cast<diagnostic_t> (i)), - m_diagnostic_count[i]); + m_diagnostic_counters.dump (out, 2); fprintf (out, " output format:\n"); m_output_format->dump (out, 4); fprintf (out, " printer:\n"); m_printer->dump (out, 4); + fprintf (out, " diagnostic buffer:\n"); + if (m_diagnostic_buffer) + m_diagnostic_buffer->dump (out, 4); + else + fprintf (out, " (none):\n"); } /* Return true if sufficiently severe diagnostics have been seen that @@ -444,9 +448,9 @@ diagnostic_context::execution_failed_p () const { /* Equivalent to (seen_error () || werrorcount), but on this context, rather than global_dc. */ - return (m_diagnostic_count [DK_ERROR] - || m_diagnostic_count [DK_SORRY] - || m_diagnostic_count [DK_WERROR]); + return (diagnostic_count (DK_ERROR) + || diagnostic_count (DK_SORRY) + || diagnostic_count (DK_WERROR)); } void @@ -756,9 +760,9 @@ diagnostic_context::check_max_errors (bool flush) if (!m_max_errors) return; - int count = (m_diagnostic_count[DK_ERROR] - + m_diagnostic_count[DK_SORRY] - + m_diagnostic_count[DK_WERROR]); + int count = (diagnostic_count (DK_ERROR) + + diagnostic_count (DK_SORRY) + + diagnostic_count (DK_WERROR)); if (count >= m_max_errors) { @@ -1292,7 +1296,7 @@ diagnostic_context::report_diagnostic (diagnostic_info *diagnostic) return false; if (diagnostic->kind != DK_NOTE && diagnostic->kind != DK_ICE) - diagnostic_check_max_errors (this); + check_max_errors (false); m_lock++; @@ -1302,8 +1306,8 @@ diagnostic_context::report_diagnostic (diagnostic_info *diagnostic) error has already occurred. This is counteracted by abort_on_error. */ if (!CHECKING_P - && (m_diagnostic_count[DK_ERROR] > 0 - || m_diagnostic_count[DK_SORRY] > 0) + && (diagnostic_count (DK_ERROR) > 0 + || diagnostic_count (DK_SORRY) > 0) && !m_abort_on_error) { expanded_location s @@ -1317,10 +1321,20 @@ diagnostic_context::report_diagnostic (diagnostic_info *diagnostic) diagnostic->message.m_format_spec, diagnostic->message.m_args_ptr); } - if (diagnostic->kind == DK_ERROR && orig_diag_kind == DK_WARNING) - ++m_diagnostic_count[DK_WERROR]; - else - ++m_diagnostic_count[diagnostic->kind]; + + /* Increment the counter for the appropriate diagnostic kind, either + within this context, or within the diagnostic_buffer. */ + { + const diagnostic_t kind_for_count = + ((diagnostic->kind == DK_ERROR && orig_diag_kind == DK_WARNING) + ? DK_WERROR + : diagnostic->kind); + diagnostic_counters &counters + = (m_diagnostic_buffer + ? m_diagnostic_buffer->m_diagnostic_counters + : m_diagnostic_counters); + ++counters.m_count_for_kind[kind_for_count]; + } /* Is this the initial diagnostic within the stack of groups? */ if (m_diagnostic_groups.m_emission_count == 0) @@ -1351,16 +1365,21 @@ diagnostic_context::report_diagnostic (diagnostic_info *diagnostic) pp_flush (m_printer); break; } - diagnostic_action_after_output (this, diagnostic->kind); + if (m_diagnostic_buffer == nullptr + || diagnostic->kind == DK_ICE + || diagnostic->kind == DK_ICE_NOBT) + action_after_output (diagnostic->kind); diagnostic->x_data = NULL; if (m_edit_context_ptr) if (diagnostic->richloc->fixits_can_be_auto_applied_p ()) - m_edit_context_ptr->add_fixits (diagnostic->richloc); + if (!m_diagnostic_buffer) + m_edit_context_ptr->add_fixits (diagnostic->richloc); m_lock--; - m_output_format->after_diagnostic (*diagnostic); + if (!m_diagnostic_buffer) + m_output_format->after_diagnostic (*diagnostic); return true; } @@ -1500,9 +1519,9 @@ diagnostic_context::error_recursion () fnotice (stderr, "internal compiler error: error reporting routines re-entered.\n"); - /* Call diagnostic_action_after_output to get the "please submit a bug - report" message. */ - diagnostic_action_after_output (this, DK_ICE); + /* Call action_after_output to get the "please submit a bug report" + message. */ + action_after_output (DK_ICE); /* Do not use gcc_unreachable here; that goes through internal_error and therefore would cause infinite recursion. */ @@ -1668,6 +1687,158 @@ set_text_art_charset (enum diagnostic_text_art_charset charset) } } +/* If BUFFER is non-null, use BUFFER as the active diagnostic_buffer on + this context. BUFFER is borrowed. + + If BUFFER is null, stop any buffering on this context until the next call + to this function. */ + +void +diagnostic_context::set_diagnostic_buffer (diagnostic_buffer *buffer) +{ + /* We don't allow changing buffering within a diagnostic group + (to simplify handling of buffered diagnostics within the + diagnostic_format implementations). */ + gcc_assert (m_diagnostic_groups.m_nesting_depth == 0); + + m_diagnostic_buffer = buffer; + + gcc_assert (m_output_format); + if (buffer) + { + buffer->ensure_per_format_buffer (); + gcc_assert (buffer->m_per_format_buffer); + m_output_format->set_buffer (buffer->m_per_format_buffer); + } + else + m_output_format->set_buffer (nullptr); +} + +/* Clear BUFFER without flushing it. */ + +void +diagnostic_context::clear_diagnostic_buffer (diagnostic_buffer &buffer) +{ + if (buffer.m_per_format_buffer) + buffer.m_per_format_buffer->clear (); + buffer.m_diagnostic_counters.clear (); + + /* We need to reset last_location, otherwise we may skip caret lines + when we actually give a diagnostic. */ + m_last_location = UNKNOWN_LOCATION; +} + +/* Flush the diagnostics in BUFFER to this context, clearing BUFFER. */ + +void +diagnostic_context::flush_diagnostic_buffer (diagnostic_buffer &buffer) +{ + bool had_errors + = (buffer.m_diagnostic_counters.m_count_for_kind[DK_ERROR] > 0 + || buffer.m_diagnostic_counters.m_count_for_kind[DK_WERROR] > 0); + if (buffer.m_per_format_buffer) + buffer.m_per_format_buffer->flush (); + buffer.m_diagnostic_counters.move_to (m_diagnostic_counters); + + action_after_output (had_errors ? DK_ERROR : DK_WARNING); + check_max_errors (true); +} + +/* struct diagnostic_counters. */ + +diagnostic_counters::diagnostic_counters () +{ + clear (); +} + +void +diagnostic_counters::dump (FILE *out, int indent) const +{ + fprintf (out, "%*scounts:\n", indent, ""); + bool none = true; + for (int i = 0; i < DK_LAST_DIAGNOSTIC_KIND; i++) + if (m_count_for_kind[i] > 0) + { + fprintf (out, "%*s%s%i\n", + indent + 2, "", + get_diagnostic_kind_text (static_cast<diagnostic_t> (i)), + m_count_for_kind[i]); + none = false; + } + if (none) + fprintf (out, "%*s(none)\n", indent + 2, ""); +} + +void +diagnostic_counters::move_to (diagnostic_counters &dest) +{ + for (int i = 0; i < DK_LAST_DIAGNOSTIC_KIND; i++) + dest.m_count_for_kind[i] += m_count_for_kind[i]; + clear (); +} + +void +diagnostic_counters::clear () +{ + memset (&m_count_for_kind, 0, sizeof m_count_for_kind); +} + +/* class diagnostic_buffer. */ + +diagnostic_buffer::diagnostic_buffer (diagnostic_context &ctxt) +: m_ctxt (ctxt), + m_per_format_buffer (nullptr) +{ +} + +diagnostic_buffer::~diagnostic_buffer () +{ + delete m_per_format_buffer; +} + +void +diagnostic_buffer::dump (FILE *out, int indent) const +{ + fprintf (out, "%*sm_per_format_buffer:\n", indent, ""); + m_diagnostic_counters.dump (out, indent + 2); + if (m_per_format_buffer) + m_per_format_buffer->dump (out, indent + 2); + else + fprintf (out, "%*s(none)\n", indent + 2, ""); +} + +bool +diagnostic_buffer::empty_p () const +{ + if (m_per_format_buffer) + return m_per_format_buffer->empty_p (); + else + return true; +} + +void +diagnostic_buffer::move_to (diagnostic_buffer &dest) +{ + ensure_per_format_buffer (); + dest.ensure_per_format_buffer (); + m_per_format_buffer->move_to (*dest.m_per_format_buffer); + m_diagnostic_counters.move_to (dest.m_diagnostic_counters); +} + +/* Lazily get output format to create its own kind of buffer. */ + +void +diagnostic_buffer::ensure_per_format_buffer () +{ + if (!m_per_format_buffer) + { + gcc_assert (m_ctxt.get_output_format ()); + m_per_format_buffer + = m_ctxt.get_output_format ()->make_per_format_buffer (); + } + gcc_assert (m_per_format_buffer); +} + /* 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. */ @@ -1997,7 +2168,6 @@ c_diagnostic_cc_tests () test_print_parseable_fixits_bytes_vs_display_columns (); test_get_location_text (); test_num_digits (); - } } // namespace selftest diff --git a/gcc/diagnostic.h b/gcc/diagnostic.h index 423e07230a652bc793d0abc4665dc34cb0640254..f1f475540de342e0297270a5447318392e4248b2 100644 --- a/gcc/diagnostic.h +++ b/gcc/diagnostic.h @@ -226,6 +226,7 @@ class diagnostic_diagram; class diagnostic_source_effect_info; class diagnostic_output_format; class diagnostic_text_output_format; +class diagnostic_buffer; /* A stack of sets of classifications: each entry in the stack is a mapping from option index to diagnostic severity that can be changed @@ -451,6 +452,25 @@ private: enum diagnostics_escape_format m_escape_format; }; +/* A collection of counters of diagnostics, per-kind + (e.g. "3 errors and 1 warning"), for use by both diagnostic_context + and by diagnostic_buffer. */ + +struct diagnostic_counters +{ + diagnostic_counters (); + + void dump (FILE *out, int indent) const; + void DEBUG_FUNCTION dump () const { dump (stderr, 0); } + + int get_count (diagnostic_t kind) const { return m_count_for_kind[kind]; } + + void move_to (diagnostic_counters &dest); + void clear (); + + int m_count_for_kind[DK_LAST_DIAGNOSTIC_KIND]; +}; + /* This data structure bundles altogether any information relevant to the context of a diagnostic message. */ class diagnostic_context @@ -521,9 +541,6 @@ public: bool report_diagnostic (diagnostic_info *); - void check_max_errors (bool flush); - void action_after_output (diagnostic_t diag_kind); - diagnostic_t classify_diagnostic (diagnostic_option_id option_id, diagnostic_t new_kind, @@ -551,7 +568,7 @@ public: void emit_diagram (const diagnostic_diagram &diagram); - const diagnostic_output_format *get_output_format () const + diagnostic_output_format *get_output_format () const { return m_output_format; } @@ -621,7 +638,11 @@ public: int &diagnostic_count (diagnostic_t kind) { - return m_diagnostic_count[kind]; + return m_diagnostic_counters.m_count_for_kind[kind]; + } + int diagnostic_count (diagnostic_t kind) const + { + return m_diagnostic_counters.get_count (kind); } /* Option-related member functions. */ @@ -679,6 +700,14 @@ public: return m_option_classifier.pch_restore (f); } + void set_diagnostic_buffer (diagnostic_buffer *); + diagnostic_buffer *get_diagnostic_buffer () const + { + return m_diagnostic_buffer; + } + void clear_diagnostic_buffer (diagnostic_buffer &); + void flush_diagnostic_buffer (diagnostic_buffer &); + private: void error_recursion () ATTRIBUTE_NORETURN; @@ -686,6 +715,9 @@ private: void get_any_inlining_info (diagnostic_info *diagnostic); + void check_max_errors (bool flush); + void action_after_output (diagnostic_t diag_kind); + /* Data members. Ideally, all of these would be private. */ @@ -698,7 +730,7 @@ private: file_cache *m_file_cache; /* The number of times we have issued diagnostics. */ - int m_diagnostic_count[DK_LAST_DIAGNOSTIC_KIND]; + diagnostic_counters m_diagnostic_counters; /* True if it has been requested that warnings be treated as errors. */ bool m_warning_as_error_requested; @@ -873,6 +905,15 @@ private: /* Owned by the context. */ char **m_original_argv; + + /* Borrowed pointer to the active diagnostic_buffer, if any. + If null (the default), then diagnostics that are reported to the + context are immediately issued to the output format. + If non-null, then diagnostics that are reported to the context + are buffered in the buffer, and may be issued to the output format + later (if the buffer is flushed), moved to other buffers, or + discarded (if the buffer is cleared). */ + diagnostic_buffer *m_diagnostic_buffer; }; inline void @@ -1082,19 +1123,6 @@ void default_diagnostic_text_finalizer (diagnostic_text_output_format &, diagnostic_t); void diagnostic_set_caret_max_width (diagnostic_context *context, int value); -inline void -diagnostic_action_after_output (diagnostic_context *context, - diagnostic_t diag_kind) -{ - context->action_after_output (diag_kind); -} - -inline void -diagnostic_check_max_errors (diagnostic_context *context, bool flush = false) -{ - context->check_max_errors (flush); -} - int get_terminal_width (void); /* Return the location associated to this diagnostic. Parameter WHICH diff --git a/gcc/fortran/error.cc b/gcc/fortran/error.cc index b27cbede1645121d821358a9c219f50d9b3c492a..64e1ce5d2472794d3da98ad04c41703fd7ab437c 100644 --- a/gcc/fortran/error.cc +++ b/gcc/fortran/error.cc @@ -43,11 +43,12 @@ static bool warnings_not_errors = false; static bool buffered_p; static gfc_error_buffer error_buffer; -/* These are always buffered buffers (.flush_p == false) to be used by - the pretty-printer. */ -static output_buffer *pp_error_buffer, *pp_warning_buffer; -static int warningcount_buffered, werrorcount_buffered; +static diagnostic_buffer *pp_error_buffer, *pp_warning_buffer; +gfc_error_buffer::gfc_error_buffer () +: flag (false), buffer (*global_dc) +{ +} /* Return a location_t suitable for 'tree' for a gfortran locus. During parsing in gfortran, loc->u.lb->location contains only the line number @@ -96,14 +97,6 @@ gfc_buffered_p (void) return buffered_p; } -/* Return true if there output_buffer is empty. */ - -static bool -gfc_output_buffer_empty_p (const output_buffer * buf) -{ - return output_buffer_last_position_in_text (buf) == NULL; -} - /* Go one level deeper suppressing errors. */ void @@ -231,19 +224,14 @@ gfc_print_wide_char (gfc_char_t c) } -/* Clear any output buffered in a pretty-print output_buffer. */ +/* Clear any output buffered in THIS_BUFFER without issuing + it to global_dc. */ static void -gfc_clear_pp_buffer (output_buffer *this_buffer) +gfc_clear_diagnostic_buffer (diagnostic_buffer *this_buffer) { - pretty_printer *pp = global_dc->m_printer; - output_buffer *tmp_buffer = pp_buffer (pp); - pp_buffer (pp) = this_buffer; - pp_clear_output_area (pp); - pp_buffer (pp) = tmp_buffer; - /* We need to reset last_location, otherwise we may skip caret lines - when we actually give a diagnostic. */ - global_dc->m_last_location = UNKNOWN_LOCATION; + gcc_assert (this_buffer); + global_dc->clear_diagnostic_buffer (*this_buffer); } /* The currently-printing diagnostic, for use by gfc_format_decoder, @@ -275,19 +263,13 @@ gfc_warning (int opt, const char *gmsgid, va_list ap) diagnostic_info diagnostic; rich_location rich_loc (line_table, UNKNOWN_LOCATION); - bool fatal_errors = global_dc->m_fatal_errors; - pretty_printer *pp = global_dc->m_printer; - output_buffer *tmp_buffer = pp_buffer (pp); + diagnostic_buffer *old_buffer = global_dc->get_diagnostic_buffer (); + gcc_assert (!old_buffer); - gfc_clear_pp_buffer (pp_warning_buffer); + gfc_clear_diagnostic_buffer (pp_warning_buffer); if (buffered_p) - { - pp_buffer (pp) = pp_warning_buffer; - global_dc->m_fatal_errors = false; - /* To prevent -fmax-errors= triggering. */ - --werrorcount; - } + global_dc->set_diagnostic_buffer (pp_warning_buffer); diagnostic_set_info (&diagnostic, gmsgid, &argp, &rich_loc, DK_WARNING); @@ -295,21 +277,7 @@ gfc_warning (int opt, const char *gmsgid, va_list ap) bool ret = gfc_report_diagnostic (&diagnostic); if (buffered_p) - { - pp_buffer (pp) = tmp_buffer; - global_dc->m_fatal_errors = fatal_errors; - - warningcount_buffered = 0; - werrorcount_buffered = 0; - /* Undo the above --werrorcount if not Werror, otherwise - werrorcount is correct already. */ - if (!ret) - ++werrorcount; - else if (diagnostic.kind == DK_ERROR) - ++werrorcount_buffered; - else - ++werrorcount, --warningcount, ++warningcount_buffered; - } + global_dc->set_diagnostic_buffer (old_buffer); va_end (argp); return ret; @@ -769,9 +737,7 @@ gfc_fatal_error (const char *gmsgid, ...) void gfc_clear_warning (void) { - gfc_clear_pp_buffer (pp_warning_buffer); - warningcount_buffered = 0; - werrorcount_buffered = 0; + gfc_clear_diagnostic_buffer (pp_warning_buffer); } @@ -781,21 +747,8 @@ gfc_clear_warning (void) void gfc_warning_check (void) { - if (! gfc_output_buffer_empty_p (pp_warning_buffer)) - { - pretty_printer *pp = global_dc->m_printer; - output_buffer *tmp_buffer = pp_buffer (pp); - pp_buffer (pp) = pp_warning_buffer; - pp_really_flush (pp); - warningcount += warningcount_buffered; - werrorcount += werrorcount_buffered; - gcc_assert (warningcount_buffered + werrorcount_buffered == 1); - pp_buffer (pp) = tmp_buffer; - diagnostic_action_after_output (global_dc, - warningcount_buffered - ? DK_WARNING : DK_ERROR); - diagnostic_check_max_errors (global_dc, true); - } + if (! pp_warning_buffer->empty_p ()) + global_dc->flush_diagnostic_buffer (*pp_warning_buffer); } @@ -806,7 +759,6 @@ gfc_error_opt (int opt, const char *gmsgid, va_list ap) { va_list argp; va_copy (argp, ap); - bool saved_abort_on_error = false; if (warnings_not_errors) { @@ -823,35 +775,19 @@ gfc_error_opt (int opt, const char *gmsgid, va_list ap) diagnostic_info diagnostic; rich_location richloc (line_table, UNKNOWN_LOCATION); - bool fatal_errors = global_dc->m_fatal_errors; - pretty_printer *pp = global_dc->m_printer; - output_buffer *tmp_buffer = pp_buffer (pp); + diagnostic_buffer *old_buffer = global_dc->get_diagnostic_buffer (); + gcc_assert (!old_buffer); - gfc_clear_pp_buffer (pp_error_buffer); + gfc_clear_diagnostic_buffer (pp_error_buffer); if (buffered_p) - { - /* To prevent -dH from triggering an abort on a buffered error, - save abort_on_error and restore it below. */ - saved_abort_on_error = global_dc->m_abort_on_error; - global_dc->m_abort_on_error = false; - pp_buffer (pp) = pp_error_buffer; - global_dc->m_fatal_errors = false; - /* To prevent -fmax-errors= triggering, we decrease it before - report_diagnostic increases it. */ - --errorcount; - } + global_dc->set_diagnostic_buffer (pp_error_buffer); diagnostic_set_info (&diagnostic, gmsgid, &argp, &richloc, DK_ERROR); gfc_report_diagnostic (&diagnostic); if (buffered_p) - { - pp_buffer (pp) = tmp_buffer; - global_dc->m_fatal_errors = fatal_errors; - global_dc->m_abort_on_error = saved_abort_on_error; - - } + global_dc->set_diagnostic_buffer (old_buffer); va_end (argp); } @@ -907,7 +843,7 @@ gfc_clear_error (void) { error_buffer.flag = false; warnings_not_errors = false; - gfc_clear_pp_buffer (pp_error_buffer); + gfc_clear_diagnostic_buffer (pp_error_buffer); } @@ -916,8 +852,8 @@ gfc_clear_error (void) bool gfc_error_flag_test (void) { - return error_buffer.flag - || !gfc_output_buffer_empty_p (pp_error_buffer); + return (error_buffer.flag + || !pp_error_buffer->empty_p ()); } @@ -928,18 +864,10 @@ bool gfc_error_check (void) { if (error_buffer.flag - || ! gfc_output_buffer_empty_p (pp_error_buffer)) + || ! pp_error_buffer->empty_p ()) { error_buffer.flag = false; - pretty_printer *pp = global_dc->m_printer; - output_buffer *tmp_buffer = pp_buffer (pp); - pp_buffer (pp) = pp_error_buffer; - pp_really_flush (pp); - ++errorcount; - gcc_assert (gfc_output_buffer_empty_p (pp_error_buffer)); - pp_buffer (pp) = tmp_buffer; - diagnostic_action_after_output (global_dc, DK_ERROR); - diagnostic_check_max_errors (global_dc, true); + global_dc->flush_diagnostic_buffer (*pp_error_buffer); return true; } @@ -954,21 +882,18 @@ static void gfc_move_error_buffer_from_to (gfc_error_buffer * buffer_from, gfc_error_buffer * buffer_to) { - output_buffer * from = &(buffer_from->buffer); - output_buffer * to = &(buffer_to->buffer); + diagnostic_buffer * from = &(buffer_from->buffer); + diagnostic_buffer * to = &(buffer_to->buffer); buffer_to->flag = buffer_from->flag; buffer_from->flag = false; - gfc_clear_pp_buffer (to); - /* We make sure this is always buffered. */ - to->m_flush_p = false; + gfc_clear_diagnostic_buffer (to); - if (! gfc_output_buffer_empty_p (from)) + if (! from->empty_p ()) { - const char *str = output_buffer_formatted_text (from); - output_buffer_append_r (to, str, strlen (str)); - gfc_clear_pp_buffer (from); + from->move_to (*to); + gfc_clear_diagnostic_buffer (from); } } @@ -995,7 +920,7 @@ gfc_pop_error (gfc_error_buffer *err) void gfc_free_error (gfc_error_buffer *err) { - gfc_clear_pp_buffer (&(err->buffer)); + gfc_clear_diagnostic_buffer (&(err->buffer)); } @@ -1028,12 +953,10 @@ gfc_diagnostics_init (void) diagnostic_format_decoder (global_dc) = gfc_format_decoder; global_dc->m_source_printing.caret_chars[0] = '1'; global_dc->m_source_printing.caret_chars[1] = '2'; - pp_warning_buffer = new (XNEW (output_buffer)) output_buffer (); - pp_warning_buffer->m_flush_p = false; + pp_warning_buffer = new diagnostic_buffer (*global_dc); /* pp_error_buffer is statically allocated. This simplifies memory management when using gfc_push/pop_error. */ pp_error_buffer = &(error_buffer.buffer); - pp_error_buffer->m_flush_p = false; } void diff --git a/gcc/fortran/gfortran.h b/gcc/fortran/gfortran.h index a55646d5604eabf9f7996ce1223a7e97f3f86930..dd599bc97a267a9b00e274c4d22d21038bca1f81 100644 --- a/gcc/fortran/gfortran.h +++ b/gcc/fortran/gfortran.h @@ -3490,12 +3490,13 @@ bool gfc_notify_std (int, const char *, ...) ATTRIBUTE_GCC_GFC(2,3); #define gfc_syntax_error(ST) \ gfc_error ("Syntax error in %s statement at %C", gfc_ascii_statement (ST)); -#include "pretty-print.h" /* For output_buffer. */ +#include "diagnostic-buffer.h" /* For diagnostic_buffer. */ struct gfc_error_buffer { bool flag; - output_buffer buffer; - gfc_error_buffer(void) : flag(false), buffer() {} + diagnostic_buffer buffer; + + gfc_error_buffer(); }; void gfc_push_error (gfc_error_buffer *); diff --git a/gcc/testsuite/gcc.dg/plugin/diagnostic_plugin_xhtml_format.c b/gcc/testsuite/gcc.dg/plugin/diagnostic_plugin_xhtml_format.c index d38250761b7379e1ec31b8c692fb44e98c8f2990..eb294761916180da1aac6d77a554133ee0dc512f 100644 --- a/gcc/testsuite/gcc.dg/plugin/diagnostic_plugin_xhtml_format.c +++ b/gcc/testsuite/gcc.dg/plugin/diagnostic_plugin_xhtml_format.c @@ -36,6 +36,7 @@ along with GCC; see the file COPYING3. If not see #include "diagnostic-diagram.h" #include "text-art/canvas.h" #include "diagnostic-format.h" +#include "diagnostic-buffer.h" #include "ordered-hash-map.h" #include "sbitmap.h" #include "make-unique.h" @@ -246,6 +247,36 @@ element::set_attr (const char *name, label_text value) } // namespace xml +class xhtml_builder; + +/* Concrete buffering implementation subclass for HTML output. */ + +class diagnostic_xhtml_format_buffer : public diagnostic_per_format_buffer +{ +public: + friend class xhtml_builder; + friend class xhtml_output_format; + + diagnostic_xhtml_format_buffer (xhtml_builder &builder) + : m_builder (builder) + {} + + void dump (FILE *out, int indent) const final override; + bool empty_p () const final override; + void move_to (diagnostic_per_format_buffer &dest) final override; + void clear () final override; + void flush () final override; + + void add_result (std::unique_ptr<xml::element> result) + { + m_results.push_back (std::move (result)); + } + +private: + xhtml_builder &m_builder; + std::vector<std::unique_ptr<xml::element>> m_results; +}; + /* A class for managing XHTML output of diagnostics. Implemented: @@ -264,12 +295,15 @@ element::set_attr (const char *name, label_text value) class xhtml_builder { public: + friend class diagnostic_xhtml_format_buffer; + xhtml_builder (diagnostic_context &context, pretty_printer &pp, const line_maps *line_maps); void on_report_diagnostic (const diagnostic_info &diagnostic, - diagnostic_t orig_diag_kind); + diagnostic_t orig_diag_kind, + diagnostic_xhtml_format_buffer *buffer); void emit_diagram (const diagnostic_diagram &diagram); void end_group (); @@ -312,6 +346,52 @@ make_span (label_text class_) return span; } +/* class diagnostic_xhtml_format_buffer : public diagnostic_per_format_buffer. */ + +void +diagnostic_xhtml_format_buffer::dump (FILE *out, int indent) const +{ + fprintf (out, "%*sdiagnostic_xhtml_format_buffer:\n", indent, ""); + int idx = 0; + for (auto &result : m_results) + { + fprintf (out, "%*sresult[%i]:\n", indent + 2, "", idx); + result->dump (out); + fprintf (out, "\n"); + ++idx; + } +} + +bool +diagnostic_xhtml_format_buffer::empty_p () const +{ + return m_results.empty (); +} + +void +diagnostic_xhtml_format_buffer::move_to (diagnostic_per_format_buffer &base) +{ + diagnostic_xhtml_format_buffer &dest + = static_cast<diagnostic_xhtml_format_buffer &> (base); + for (auto &&result : m_results) + dest.m_results.push_back (std::move (result)); + m_results.clear (); +} + +void +diagnostic_xhtml_format_buffer::clear () +{ + m_results.clear (); +} + +void +diagnostic_xhtml_format_buffer::flush () +{ + for (auto &&result : m_results) + m_builder.m_diagnostics_element->add_child (std::move (result)); + m_results.clear (); +} + /* class xhtml_builder. */ /* xhtml_builder's ctor. */ @@ -360,7 +440,8 @@ xhtml_builder::xhtml_builder (diagnostic_context &context, void xhtml_builder::on_report_diagnostic (const diagnostic_info &diagnostic, - diagnostic_t orig_diag_kind) + diagnostic_t orig_diag_kind, + diagnostic_xhtml_format_buffer *buffer) { if (diagnostic.kind == DK_ICE || diagnostic.kind == DK_ICE_NOBT) { @@ -374,12 +455,20 @@ xhtml_builder::on_report_diagnostic (const diagnostic_info &diagnostic, auto diag_element = make_element_for_diagnostic (diagnostic, orig_diag_kind); - if (m_cur_diagnostic_element) - /* Nested diagnostic. */ - m_cur_diagnostic_element->add_child (std::move (diag_element)); + if (buffer) + { + gcc_assert (!m_cur_diagnostic_element); + buffer->m_results.push_back (std::move (diag_element)); + } else - /* Top-level diagnostic. */ - m_cur_diagnostic_element = std::move (diag_element); + { + if (m_cur_diagnostic_element) + /* Nested diagnostic. */ + m_cur_diagnostic_element->add_child (std::move (diag_element)); + else + /* Top-level diagnostic. */ + m_cur_diagnostic_element = std::move (diag_element); + } } std::unique_ptr<xml::element> @@ -596,10 +685,21 @@ public: void dump (FILE *out, int indent) const override { - fprintf (out, "%*xhtml_output_format\n", indent, ""); + fprintf (out, "%*sxhtml_output_format\n", indent, ""); diagnostic_output_format::dump (out, indent); } + diagnostic_per_format_buffer *make_per_format_buffer () final override + { + return new diagnostic_xhtml_format_buffer (m_builder); + } + void set_buffer (diagnostic_per_format_buffer *base_buffer) final override + { + diagnostic_xhtml_format_buffer *buffer + = static_cast<diagnostic_xhtml_format_buffer *> (base_buffer); + m_buffer = buffer; + } + void on_begin_group () final override { /* No-op, */ @@ -610,9 +710,9 @@ public: } void on_report_diagnostic (const diagnostic_info &diagnostic, - diagnostic_t orig_diag_kind) final override + diagnostic_t orig_diag_kind) final override { - m_builder.on_report_diagnostic (diagnostic, orig_diag_kind); + m_builder.on_report_diagnostic (diagnostic, orig_diag_kind, m_buffer); } void on_diagram (const diagnostic_diagram &diagram) final override { @@ -632,10 +732,12 @@ protected: xhtml_output_format (diagnostic_context &context, const line_maps *line_maps) : diagnostic_output_format (context), - m_builder (context, *get_printer (), line_maps) + m_builder (context, *get_printer (), line_maps), + m_buffer (nullptr) {} xhtml_builder m_builder; + diagnostic_xhtml_format_buffer *m_buffer; }; class xhtml_stream_output_format : public xhtml_output_format diff --git a/gcc/testsuite/gfortran.dg/diagnostic-format-json-pr105916.F90 b/gcc/testsuite/gfortran.dg/diagnostic-format-json-pr105916.F90 new file mode 100644 index 0000000000000000000000000000000000000000..bf22a86867bc38328ccc3f7fed6e9971572cbdb4 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/diagnostic-format-json-pr105916.F90 @@ -0,0 +1,14 @@ +! { dg-do compile } +! { dg-options "-fdiagnostics-format=json-stderr -fmax-errors=1 -Wfatal-errors" } + +program main + implicit none + print*, "Hello World!" +end program main + +! We expect an empty array as the JSON output. +#if 0 +{ dg-begin-multiline-output "" } +[] +{ dg-end-multiline-output "" } +#endif diff --git a/gcc/testsuite/gfortran.dg/diagnostic-format-sarif-1.F90 b/gcc/testsuite/gfortran.dg/diagnostic-format-sarif-1.F90 new file mode 100644 index 0000000000000000000000000000000000000000..bea04b86a9b69a920968ef5a2251ca6b6997045e --- /dev/null +++ b/gcc/testsuite/gfortran.dg/diagnostic-format-sarif-1.F90 @@ -0,0 +1,18 @@ +! { dg-do compile } +! { dg-options "-fdiagnostics-format=sarif-file" } + +#error message + +! Verify that some JSON was written to a file with the expected name. +! { dg-final { verify-sarif-file } } */ + +! We expect a failing compile due to the error, but the use of +! -fdiagnostics-format=sarif-file means there should be no output to stderr. +! DejaGnu injects this message; ignore it: +! +! { dg-prune-output "exit status is 1" } + + +! Use a Python script to verify various properties about the generated +! .sarif file: +! { dg-final { run-sarif-pytest diagnostic-format-sarif-1.F90 "diagnostic-format-sarif-1.py" } } diff --git a/gcc/testsuite/gfortran.dg/diagnostic-format-sarif-1.py b/gcc/testsuite/gfortran.dg/diagnostic-format-sarif-1.py new file mode 100644 index 0000000000000000000000000000000000000000..26cb4654741288fa4d1bcf17dbb0c6c3d6f6f9a9 --- /dev/null +++ b/gcc/testsuite/gfortran.dg/diagnostic-format-sarif-1.py @@ -0,0 +1,53 @@ +from sarif import * + +import pytest + +@pytest.fixture(scope='function', autouse=True) +def sarif(): + return sarif_from_env() + +def test_basics(sarif): + schema = sarif['$schema'] + assert schema == "https://docs.oasis-open.org/sarif/sarif/v2.1.0/errata01/os/schemas/sarif-schema-2.1.0.json" + + version = sarif['version'] + assert version == "2.1.0" + +def test_execution_unsuccessful(sarif): + runs = sarif['runs'] + run = runs[0] + + invocations = run['invocations'] + assert len(invocations) == 1 + invocation = invocations[0] + + # We expect the 'error' to make executionSuccessful be false + assert invocation['executionSuccessful'] == False + +def test_error(sarif): + runs = sarif['runs'] + run = runs[0] + results = run['results'] + + # We expect a single error + # + # . The textual form of the diagnostic would look like this: + # . PATH/diagnostic-format-sarif-1.F90:4:2: + # . + # . 4 | #error message + # . | 1~~~~ + # . Error: #error message + assert len(results) == 1 + + result = results[0] + assert result['level'] == 'error' + assert result['message']['text'] == "#error message" + locations = result['locations'] + assert len(locations) == 1 + + location = locations[0] + assert get_location_artifact_uri(location).endswith('diagnostic-format-sarif-1.F90') + assert get_location_snippet_text(location) == '#error message\n' + assert get_location_physical_region(location)['startLine'] == 4 + assert get_location_physical_region(location)['startColumn'] == 2 + assert get_location_physical_region(location)['endColumn'] == 7 diff --git a/gcc/testsuite/gfortran.dg/diagnostic-format-sarif-pr105916.f90 b/gcc/testsuite/gfortran.dg/diagnostic-format-sarif-pr105916.f90 new file mode 100644 index 0000000000000000000000000000000000000000..4d9734a1352c0ee415572d1ab2b86da63b901d0c --- /dev/null +++ b/gcc/testsuite/gfortran.dg/diagnostic-format-sarif-pr105916.f90 @@ -0,0 +1,13 @@ +! { dg-options "-fdiagnostics-format=sarif-file -fmax-errors=1 -Wfatal-errors" } + +program main + implicit none + print*, "Hello World!" +end program main + +! Verify that some JSON was written to a file with the expected name. +! { dg-final { verify-sarif-file } } */ + +! We expect a successful invocation and no results: +! { dg-final { scan-sarif-file "\"executionSuccessful\": true" } } +! { dg-final { scan-sarif-file "\"results\": \\\[\\\]" } }