From 34f01475611b422668a70744c79273c7019625f2 Mon Sep 17 00:00:00 2001 From: David Malcolm <dmalcolm@redhat.com> Date: Tue, 3 Sep 2024 15:10:56 -0400 Subject: [PATCH] pretty-print: naming cleanups This patch is a followup to r15-3311-ge31b6176996567 making some cleanups to pretty-printing to reflect those changes: - renaming "chunk_info" to "pp_formatted_chunks" - renaming "cur_chunk_array" to "m_cur_fomatted_chunks" - rewording/clarifying comments and taking the opportunity to add a "m_" prefix to all fields of output_buffer. No functional change intended. gcc/analyzer/ChangeLog: * analyzer-logging.cc (logger::logger): Prefix all output_buffer fields with "m_". gcc/c-family/ChangeLog: * c-ada-spec.cc (dump_ada_node): Prefix all output_buffer fields with "m_". * c-pretty-print.cc (pp_c_integer_constant): Likewise. (pp_c_integer_constant): Likewise. (pp_c_floating_constant): Likewise. (pp_c_fixed_constant): Likewise. gcc/c/ChangeLog: * c-objc-common.cc (print_type): Prefix all output_buffer fields with "m_". gcc/cp/ChangeLog: * error.cc (type_to_string): Prefix all output_buffer fields with "m_". (append_formatted_chunk): Likewise. Rename "chunk_info" to "pp_formatted_chunks" and field cur_chunk_array with m_cur_formatted_chunks. gcc/fortran/ChangeLog: * error.cc (gfc_move_error_buffer_from_to): Prefix all output_buffer fields with "m_". (gfc_diagnostics_init): Likewise. gcc/ChangeLog: * diagnostic.cc (diagnostic_set_caret_max_width): Prefix all output_buffer fields with "m_". * dumpfile.cc (emit_any_pending_textual_chunks): Likewise. (emit_any_pending_textual_chunks): Likewise. * gimple-pretty-print.cc (gimple_dump_bb_buff): Likewise. * json.cc (value::dump): Likewise. * pretty-print-format-impl.h (class chunk_info): Rename to... (class pp_formatted_chunks): ...this. Add friend class output_buffer. Update comment near end of decl to show the pp_formatted_chunks instance on the chunk_obstack. (pp_formatted_chunks::pop_from_output_buffer): Delete decl. (pp_formatted_chunks::on_begin_quote): Delete decl that should have been removed in r15-3311-ge31b6176996567. (pp_formatted_chunks::on_end_quote): Likewise. (pp_formatted_chunks::m_prev): Update for renaming. * pretty-print.cc (output_buffer::output_buffer): Prefix all fields with "m_". Rename "cur_chunk_array" to "m_cur_formatted_chunks". (output_buffer::~output_buffer): Prefix all fields with "m_". (output_buffer::push_formatted_chunks): New. (output_buffer::pop_formatted_chunks): New. (pp_write_text_to_stream): Prefix all output_buffer fields with "m_". (pp_write_text_as_dot_label_to_stream): Likewise. (pp_write_text_as_html_like_dot_to_stream): Likewise. (chunk_info::append_formatted_chunk): Rename to... (pp_formatted_chunks::append_formatted_chunk): ...this. (chunk_info::pop_from_output_buffer): Delete. (pretty_printer::format): Update leading comment to mention pushing pp_formatted_chunks, and to reflect changes in r15-3311-ge31b6176996567. Prefix all output_buffer fields with "m_". (pp_output_formatted_text): Update leading comment to mention popping a pp_formatted_chunks, and to reflect the changes in r15-3311-ge31b6176996567. Prefix all output_buffer fields with "m_" and rename "cur_chunk_array" to "m_cur_formatted_chunks". Replace call to chunk_info::pop_from_output_buffer with a call to output_buffer::pop_formatted_chunks. (pp_flush): Prefix all output_buffer fields with "m_". (pp_really_flush): Likewise. (pp_clear_output_area): Likewise. (pp_append_text): Likewise. (pretty_printer::remaining_character_count_for_line): Likewise. (pp_newline): Likewise. (pp_character): Likewise. (pp_markup::context::push_back_any_text): Likewise. * pretty-print.h (class chunk_info): Rename to... (class pp_formatted_chunks): ...this. (class output_buffer): Delete unimplemented rule-of-5 members. (output_buffer::push_formatted_chunks): New decl. (output_buffer::pop_formatted_chunks): New decl. (output_buffer::formatted_obstack): Rename to... (output_buffer::m_formatted_obstack): ...this. (output_buffer::chunk_obstack): Rename to... (output_buffer::m_chunk_obstack): ...this. (output_buffer::obstack): Rename to... (output_buffer::m_obstack): ...this. (output_buffer::cur_chunk_array): Rename to... (output_buffer::m_cur_formatted_chunks): ...this. (output_buffer::stream): Rename to... (output_buffer::m_stream): ...this. (output_buffer::line_length): Rename to... (output_buffer::m_line_length): ...this. (output_buffer::digit_buffer): Rename to... (output_buffer::m_digit_buffer): ...this. (output_buffer::flush_p): Rename to... (output_buffer::m_flush_p): ...this. (output_buffer_formatted_text): Prefix all output_buffer fields with "m_". (output_buffer_append_r): Likewise. (output_buffer_last_position_in_text): Likewise. (pretty_printer::set_output_stream): Likewise. (pp_scalar): Likewise. (pp_wide_int): Likewise. * tree-pretty-print.cc (dump_generic_node): Likewise. (dump_generic_node): Likewise. (pp_double_int): Likewise. Signed-off-by: David Malcolm <dmalcolm@redhat.com> --- gcc/analyzer/analyzer-logging.cc | 2 +- gcc/c-family/c-ada-spec.cc | 6 +- gcc/c-family/c-pretty-print.cc | 18 +-- gcc/c/c-objc-common.cc | 4 +- gcc/cp/error.cc | 6 +- gcc/diagnostic.cc | 2 +- gcc/dumpfile.cc | 6 +- gcc/fortran/error.cc | 6 +- gcc/gimple-pretty-print.cc | 2 +- gcc/json.cc | 2 +- gcc/pretty-print-format-impl.h | 34 +++--- gcc/pretty-print.cc | 192 +++++++++++++++++-------------- gcc/pretty-print.h | 52 +++++---- gcc/tree-pretty-print.cc | 10 +- 14 files changed, 182 insertions(+), 160 deletions(-) diff --git a/gcc/analyzer/analyzer-logging.cc b/gcc/analyzer/analyzer-logging.cc index cceb4fe24a55..d3b04f2d9b10 100644 --- a/gcc/analyzer/analyzer-logging.cc +++ b/gcc/analyzer/analyzer-logging.cc @@ -51,7 +51,7 @@ logger::logger (FILE *f_out, m_pp (reference_pp.clone ()) { pp_show_color (m_pp) = 0; - pp_buffer (m_pp)->stream = f_out; + pp_buffer (m_pp)->m_stream = f_out; /* %qE in logs for SSA_NAMEs should show the ssa names, rather than trying to prettify things by showing the underlying var. */ diff --git a/gcc/c-family/c-ada-spec.cc b/gcc/c-family/c-ada-spec.cc index e1b1b2a4b73f..fbba44362540 100644 --- a/gcc/c-family/c-ada-spec.cc +++ b/gcc/c-family/c-ada-spec.cc @@ -2485,13 +2485,13 @@ dump_ada_node (pretty_printer *pp, tree node, tree type, int spc, pp_minus (pp); val = -val; } - sprintf (pp_buffer (pp)->digit_buffer, + sprintf (pp_buffer (pp)->m_digit_buffer, "16#%" HOST_WIDE_INT_PRINT "x", val.elt (val.get_len () - 1)); for (i = val.get_len () - 2; i >= 0; i--) - sprintf (pp_buffer (pp)->digit_buffer, + sprintf (pp_buffer (pp)->m_digit_buffer, HOST_WIDE_INT_PRINT_PADDED_HEX, val.elt (i)); - pp_string (pp, pp_buffer (pp)->digit_buffer); + pp_string (pp, pp_buffer (pp)->m_digit_buffer); } break; diff --git a/gcc/c-family/c-pretty-print.cc b/gcc/c-family/c-pretty-print.cc index dd7eba123943..26038818d759 100644 --- a/gcc/c-family/c-pretty-print.cc +++ b/gcc/c-family/c-pretty-print.cc @@ -1043,7 +1043,7 @@ pp_c_integer_constant (c_pretty_printer *pp, tree i) wi = -wi; } unsigned int prec = wi.get_precision (); - if ((prec + 3) / 4 > sizeof (pp_buffer (pp)->digit_buffer) - 3) + if ((prec + 3) / 4 > sizeof (pp_buffer (pp)->m_digit_buffer) - 3) { char *buf = XALLOCAVEC (char, (prec + 3) / 4 + 3); print_hex (wi, buf); @@ -1051,8 +1051,8 @@ pp_c_integer_constant (c_pretty_printer *pp, tree i) } else { - print_hex (wi, pp_buffer (pp)->digit_buffer); - pp_string (pp, pp_buffer (pp)->digit_buffer); + print_hex (wi, pp_buffer (pp)->m_digit_buffer); + pp_string (pp, pp_buffer (pp)->m_digit_buffer); } } } @@ -1138,11 +1138,11 @@ pp_c_floating_constant (c_pretty_printer *pp, tree r) log10(2) to 7 significant digits. */ int max_digits10 = 2 + (is_decimal ? fmt->p : fmt->p * 643L / 2136); - real_to_decimal (pp_buffer (pp)->digit_buffer, &TREE_REAL_CST (r), - sizeof (pp_buffer (pp)->digit_buffer), + real_to_decimal (pp_buffer (pp)->m_digit_buffer, &TREE_REAL_CST (r), + sizeof (pp_buffer (pp)->m_digit_buffer), max_digits10, 1); - pp_string (pp, pp_buffer(pp)->digit_buffer); + pp_string (pp, pp_buffer(pp)->m_digit_buffer); if (TREE_TYPE (r) == float_type_node) pp_character (pp, 'f'); else if (TREE_TYPE (r) == long_double_type_node) @@ -1170,9 +1170,9 @@ pp_c_floating_constant (c_pretty_printer *pp, tree r) static void pp_c_fixed_constant (c_pretty_printer *pp, tree r) { - fixed_to_decimal (pp_buffer (pp)->digit_buffer, &TREE_FIXED_CST (r), - sizeof (pp_buffer (pp)->digit_buffer)); - pp_string (pp, pp_buffer(pp)->digit_buffer); + fixed_to_decimal (pp_buffer (pp)->m_digit_buffer, &TREE_FIXED_CST (r), + sizeof (pp_buffer (pp)->m_digit_buffer)); + pp_string (pp, pp_buffer(pp)->m_digit_buffer); } /* Pretty-print a compound literal expression. GNU extensions include diff --git a/gcc/c/c-objc-common.cc b/gcc/c/c-objc-common.cc index 9d39fcd4e442..afd3e72b2e99 100644 --- a/gcc/c/c-objc-common.cc +++ b/gcc/c/c-objc-common.cc @@ -236,7 +236,7 @@ print_type (c_pretty_printer *cpp, tree t, bool *quoted, highlight_color = nullptr; gcc_assert (TYPE_P (t)); - struct obstack *ob = pp_buffer (cpp)->obstack; + struct obstack *ob = pp_buffer (cpp)->m_obstack; char *p = (char *) obstack_base (ob); /* Remember the end of the initial dump. */ int len = obstack_object_size (ob); @@ -258,7 +258,7 @@ print_type (c_pretty_printer *cpp, tree t, bool *quoted, c_pretty_printer cpp2; /* Print the stripped version into a temporary printer. */ cpp2.type_id (aka_type); - struct obstack *ob2 = pp_buffer (&cpp2)->obstack; + struct obstack *ob2 = pp_buffer (&cpp2)->m_obstack; /* Get the stripped version from the temporary printer. */ const char *aka = (char *) obstack_base (ob2); int aka_len = obstack_object_size (ob2); diff --git a/gcc/cp/error.cc b/gcc/cp/error.cc index 420fad26b7b7..57cd76caf490 100644 --- a/gcc/cp/error.cc +++ b/gcc/cp/error.cc @@ -3533,7 +3533,7 @@ type_to_string (tree typ, int verbose, bool postprocessed, bool *quote, pp_string (cxx_pp, colorize_start (show_color, highlight_color)); } - struct obstack *ob = pp_buffer (cxx_pp)->obstack; + struct obstack *ob = pp_buffer (cxx_pp)->m_obstack; int type_start, type_len; type_start = obstack_object_size (ob); @@ -4430,8 +4430,8 @@ static void append_formatted_chunk (pretty_printer *pp, const char *content) { output_buffer *buffer = pp_buffer (pp); - chunk_info *chunk_array = buffer->cur_chunk_array; - chunk_array->append_formatted_chunk (buffer->chunk_obstack, content); + pp_formatted_chunks *chunk_array = buffer->m_cur_formatted_chunks; + chunk_array->append_formatted_chunk (buffer->m_chunk_obstack, content); } #if __GNUC__ >= 10 diff --git a/gcc/diagnostic.cc b/gcc/diagnostic.cc index a80e16b542df..58d645852ebd 100644 --- a/gcc/diagnostic.cc +++ b/gcc/diagnostic.cc @@ -126,7 +126,7 @@ diagnostic_set_caret_max_width (diagnostic_context *context, int value) { /* One minus to account for the leading empty space. */ value = value ? value - 1 - : (isatty (fileno (pp_buffer (context->printer)->stream)) + : (isatty (fileno (pp_buffer (context->printer)->m_stream)) ? get_terminal_width () - 1: INT_MAX); if (value <= 0) diff --git a/gcc/dumpfile.cc b/gcc/dumpfile.cc index da3671829a21..074da7df2169 100644 --- a/gcc/dumpfile.cc +++ b/gcc/dumpfile.cc @@ -1006,7 +1006,7 @@ emit_any_pending_textual_chunks () { dump_pretty_printer *pp = &m_dump_pp; output_buffer *const buffer = pp_buffer (pp); - gcc_assert (buffer->obstack == &buffer->formatted_obstack); + gcc_assert (buffer->m_obstack == &buffer->m_formatted_obstack); /* Don't emit an item if the pending text is empty. */ if (output_buffer_last_position_in_text (buffer) == nullptr) @@ -1020,8 +1020,8 @@ emit_any_pending_textual_chunks () /* Clear the pending text by unwinding formatted_text back to the start of the buffer (without deallocating). */ - obstack_free (&buffer->formatted_obstack, - buffer->formatted_obstack.object_base); + obstack_free (&buffer->m_formatted_obstack, + buffer->m_formatted_obstack.object_base); } /* Output a formatted message using FORMAT on appropriate dump streams. */ diff --git a/gcc/fortran/error.cc b/gcc/fortran/error.cc index a5884620e301..ffe95d19a62d 100644 --- a/gcc/fortran/error.cc +++ b/gcc/fortran/error.cc @@ -1640,7 +1640,7 @@ gfc_move_error_buffer_from_to (gfc_error_buffer * buffer_from, gfc_clear_pp_buffer (to); /* We make sure this is always buffered. */ - to->flush_p = false; + to->m_flush_p = false; if (! gfc_output_buffer_empty_p (from)) { @@ -1707,11 +1707,11 @@ gfc_diagnostics_init (void) 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->flush_p = false; + pp_warning_buffer->m_flush_p = false; /* 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->flush_p = false; + pp_error_buffer->m_flush_p = false; } void diff --git a/gcc/gimple-pretty-print.cc b/gcc/gimple-pretty-print.cc index 08b823c84eff..01d7c9f6eebd 100644 --- a/gcc/gimple-pretty-print.cc +++ b/gcc/gimple-pretty-print.cc @@ -3076,7 +3076,7 @@ gimple_dump_bb_buff (pretty_printer *pp, basic_block bb, int indent, pp_newline_and_flush (pp); gcc_checking_assert (DECL_STRUCT_FUNCTION (current_function_decl)); dump_histograms_for_stmt (DECL_STRUCT_FUNCTION (current_function_decl), - pp_buffer (pp)->stream, stmt); + pp_buffer (pp)->m_stream, stmt); } dump_implicit_edges (pp, bb, indent, flags); diff --git a/gcc/json.cc b/gcc/json.cc index 275ef486faf1..23c8bf1cad39 100644 --- a/gcc/json.cc +++ b/gcc/json.cc @@ -87,7 +87,7 @@ void value::dump (FILE *outf, bool formatted) const { pretty_printer pp; - pp_buffer (&pp)->stream = outf; + pp_buffer (&pp)->m_stream = outf; print (&pp, formatted); pp_flush (&pp); } diff --git a/gcc/pretty-print-format-impl.h b/gcc/pretty-print-format-impl.h index f1996284f4a1..c70f61ce1bab 100644 --- a/gcc/pretty-print-format-impl.h +++ b/gcc/pretty-print-format-impl.h @@ -56,7 +56,7 @@ along with GCC; see the file COPYING3. If not see To avoid needing lots of heap allocation/deallocation, pp_token instances are allocated in the pretty_printer's chunk_obstack: they must not outlive phase 3 of formatting of the given - chunk_info level. */ + pp_formatted_chunks level. */ struct pp_token { @@ -317,8 +317,8 @@ public: pp_token &operator= (pp_token_list &&) = delete; /* Make a pp_token of the given subclass, using the relevant obstack to provide - the memory. The pp_token must therefore not outlive the current chunk_info - level during formatting. */ + the memory. The pp_token must therefore not outlive the current + pp_formatted_chunks level during formatting. */ template<typename Subclass, typename... Args> std::unique_ptr<pp_token> make_token (Args&&... args) @@ -357,43 +357,33 @@ public: pp_token *m_end; }; -/* The chunk_info data structure forms a stack of the results from the +/* The pp_formatted_chunks data structure forms a stack of the results from the first phase of formatting (pp_format) which have not yet been output (pp_output_formatted_text). A stack is necessary because the diagnostic starter may decide to generate its own output by way of the formatter. */ -class chunk_info +class pp_formatted_chunks { friend class pretty_printer; friend class pp_markup::context; + friend class output_buffer; public: pp_token_list * const * get_token_lists () const { return m_args; } void append_formatted_chunk (obstack &s, const char *content); - void pop_from_output_buffer (output_buffer &buf); - void dump (FILE *out) const; void DEBUG_FUNCTION dump () const { dump (stderr); } private: - void on_begin_quote (const output_buffer &buf, - unsigned chunk_idx, - const urlifier *urlifier); - - void on_end_quote (pretty_printer *pp, - output_buffer &buf, - unsigned chunk_idx, - const urlifier *urlifier); - - /* Pointer to previous chunk on the stack. */ - chunk_info *m_prev; + /* Pointer to previous level on the stack. */ + pp_formatted_chunks *m_prev; /* Array of chunks to output. Each chunk is a doubly-linked list of pp_token. - The chunks can be printed via chunk_info::dump (). + The chunks can be printed via pp_formatted_chunks::dump (). In the first phase of formatting, even-numbered chunks are to be output verbatim, odd-numbered chunks are format specifiers. @@ -456,7 +446,9 @@ private: example, the in-memory layout of the chunk_obstack might look like this after phase 1: - + pp_token_list for chunk 0 (m_first: *) <--- START of chunk_info level + + pp_formatted_chunks instance <--- START of pp_formatted_chunks level + | + + pp_token_list for chunk 0 (m_first: *) | | + "foo: \0" <-------------\ | | | | @@ -483,7 +475,7 @@ private: At each stage, allocation of additional text buffers, tokens, and lists grow forwards in the obstack (though the internal pointers in linked lists might point backwards to earlier objects within the same - chunk_info level). */ + pp_formatted_chunks level). */ }; #endif /* GCC_PRETTY_PRINT_FORMAT_IMPL_H */ diff --git a/gcc/pretty-print.cc b/gcc/pretty-print.cc index fe6b6090f323..50aea69edd62 100644 --- a/gcc/pretty-print.cc +++ b/gcc/pretty-print.cc @@ -741,25 +741,53 @@ text_info::get_location (unsigned int index_of_location) const // Default construct an output buffer. output_buffer::output_buffer () - : formatted_obstack (), - chunk_obstack (), - obstack (&formatted_obstack), - cur_chunk_array (), - stream (stderr), - line_length (), - digit_buffer (), - flush_p (true) + : m_formatted_obstack (), + m_chunk_obstack (), + m_obstack (&m_formatted_obstack), + m_cur_formatted_chunks (nullptr), + m_stream (stderr), + m_line_length (), + m_digit_buffer (), + m_flush_p (true) { - obstack_init (&formatted_obstack); - obstack_init (&chunk_obstack); + obstack_init (&m_formatted_obstack); + obstack_init (&m_chunk_obstack); } // Release resources owned by an output buffer at the end of lifetime. output_buffer::~output_buffer () { - obstack_free (&chunk_obstack, NULL); - obstack_free (&formatted_obstack, NULL); + obstack_free (&m_chunk_obstack, NULL); + obstack_free (&m_formatted_obstack, NULL); +} + +/* Allocate a new pp_formatted_chunks from chunk_obstack and push + it onto this buffer's stack. + This represents the result of phases 1 and 2 of formatting. */ + +pp_formatted_chunks * +output_buffer::push_formatted_chunks () +{ + /* Allocate a new chunk structure. */ + pp_formatted_chunks *new_chunk_array + = XOBNEW (&m_chunk_obstack, pp_formatted_chunks); + new_chunk_array->m_prev = m_cur_formatted_chunks; + m_cur_formatted_chunks = new_chunk_array; + return new_chunk_array; +} + +/* Deallocate the current pp_formatted_chunks structure and everything after it + (i.e. the associated series of formatted strings, pp_token_lists, and + pp_tokens). */ + +void +output_buffer::pop_formatted_chunks () +{ + pp_formatted_chunks *old_top = m_cur_formatted_chunks; + gcc_assert (old_top); + m_cur_formatted_chunks = old_top->m_prev; + obstack_free (&m_chunk_obstack, old_top); } #ifndef PTRDIFF_MAX @@ -885,9 +913,9 @@ pp_write_text_to_stream (pretty_printer *pp) { const char *text = pp_formatted_text (pp); #ifdef __MINGW32__ - mingw_ansi_fputs (text, pp_buffer (pp)->stream); + mingw_ansi_fputs (text, pp_buffer (pp)->m_stream); #else - fputs (text, pp_buffer (pp)->stream); + fputs (text, pp_buffer (pp)->m_stream); #endif pp_clear_output_area (pp); } @@ -906,7 +934,7 @@ pp_write_text_as_dot_label_to_stream (pretty_printer *pp, bool for_record) { const char *text = pp_formatted_text (pp); const char *p = text; - FILE *fp = pp_buffer (pp)->stream; + FILE *fp = pp_buffer (pp)->m_stream; for (;*p; p++) { @@ -975,7 +1003,7 @@ pp_write_text_as_html_like_dot_to_stream (pretty_printer *pp) { const char *text = pp_formatted_text (pp); const char *p = text; - FILE *fp = pp_buffer (pp)->stream; + FILE *fp = pp_buffer (pp)->m_stream; for (;*p; p++) { @@ -1473,7 +1501,7 @@ pp_token_list::dump (FILE *out) const will be printed by pp_output_formatted_text. */ void -chunk_info::append_formatted_chunk (obstack &s, const char *content) +pp_formatted_chunks::append_formatted_chunk (obstack &s, const char *content) { unsigned int chunk_idx; for (chunk_idx = 0; m_args[chunk_idx]; chunk_idx++) @@ -1484,18 +1512,8 @@ chunk_info::append_formatted_chunk (obstack &s, const char *content) m_args[chunk_idx] = nullptr; } -/* Deallocate the current chunk structure and everything after it (i.e. the - associated series of formatted strings). */ - -void -chunk_info::pop_from_output_buffer (output_buffer &buf) -{ - buf.cur_chunk_array = m_prev; - obstack_free (&buf.chunk_obstack, this); -} - void -chunk_info::dump (FILE *out) const +pp_formatted_chunks::dump (FILE *out) const { for (size_t idx = 0; m_args[idx]; ++idx) { @@ -1564,9 +1582,12 @@ push_back_any_text (pp_token_list *tok_list, A format string can have at most 30 arguments. */ /* Implementation of pp_format. - Formatting phases 1 and 2: render TEXT->format_spec plus - text->m_args_ptr into a series of chunks in pp_buffer (PP)->args[]. - Phase 3 is in pp_output_formatted_text. */ + Formatting phases 1 and 2: + - push a pp_formatted_chunks instance. + - render TEXT->format_spec plus text->m_args_ptr into the pp_formatted_chunks + instance as pp_token_lists. + Phase 3 is in pp_output_formatted_text, which pops the pp_formatted_chunks + instance. */ void pretty_printer::format (text_info *text) @@ -1576,11 +1597,7 @@ pretty_printer::format (text_info *text) unsigned int chunk = 0, argno; pp_token_list **formatters[PP_NL_ARGMAX]; - /* Allocate a new chunk structure. */ - chunk_info *new_chunk_array = XOBNEW (&buffer->chunk_obstack, chunk_info); - - new_chunk_array->m_prev = buffer->cur_chunk_array; - buffer->cur_chunk_array = new_chunk_array; + pp_formatted_chunks *new_chunk_array = buffer->push_formatted_chunks (); pp_token_list **args = new_chunk_array->m_args; /* Formatting phase 1: split up TEXT->format_spec into chunks in @@ -1594,12 +1611,13 @@ pretty_printer::format (text_info *text) unsigned int curarg = 0; bool any_unnumbered = false, any_numbered = false; pp_token_list *cur_token_list; - args[chunk++] = cur_token_list = pp_token_list::make (buffer->chunk_obstack); + args[chunk++] = cur_token_list + = pp_token_list::make (buffer->m_chunk_obstack); for (const char *p = text->m_format_spec; *p; ) { while (*p != '\0' && *p != '%') { - obstack_1grow (&buffer->chunk_obstack, *p); + obstack_1grow (&buffer->m_chunk_obstack, *p); p++; } @@ -1612,13 +1630,13 @@ pretty_printer::format (text_info *text) gcc_unreachable (); case '%': - obstack_1grow (&buffer->chunk_obstack, '%'); + obstack_1grow (&buffer->m_chunk_obstack, '%'); p++; continue; case '<': { - push_back_any_text (cur_token_list, &buffer->chunk_obstack); + push_back_any_text (cur_token_list, &buffer->m_chunk_obstack); cur_token_list->push_back<pp_token_begin_quote> (); p++; continue; @@ -1626,14 +1644,14 @@ pretty_printer::format (text_info *text) case '>': { - push_back_any_text (cur_token_list, &buffer->chunk_obstack); + push_back_any_text (cur_token_list, &buffer->m_chunk_obstack); cur_token_list->push_back<pp_token_end_quote> (); p++; continue; } case '\'': { - push_back_any_text (cur_token_list, &buffer->chunk_obstack); + push_back_any_text (cur_token_list, &buffer->m_chunk_obstack); cur_token_list->push_back<pp_token_end_quote> (); p++; } @@ -1641,7 +1659,7 @@ pretty_printer::format (text_info *text) case '}': { - push_back_any_text (cur_token_list, &buffer->chunk_obstack); + push_back_any_text (cur_token_list, &buffer->m_chunk_obstack); cur_token_list->push_back<pp_token_end_url> (); p++; } @@ -1649,7 +1667,7 @@ pretty_printer::format (text_info *text) case 'R': { - push_back_any_text (cur_token_list, &buffer->chunk_obstack); + push_back_any_text (cur_token_list, &buffer->m_chunk_obstack); cur_token_list->push_back<pp_token_end_color> (); p++; continue; @@ -1658,20 +1676,20 @@ pretty_printer::format (text_info *text) case 'm': { const char *errstr = xstrerror (text->m_err_no); - obstack_grow (&buffer->chunk_obstack, errstr, strlen (errstr)); + obstack_grow (&buffer->m_chunk_obstack, errstr, strlen (errstr)); } p++; continue; default: /* Handled in phase 2. Terminate the plain chunk here. */ - push_back_any_text (cur_token_list, &buffer->chunk_obstack); + push_back_any_text (cur_token_list, &buffer->m_chunk_obstack); break; } /* Start a new token list for the formatting args. */ args[chunk] = cur_token_list - = pp_token_list::make (buffer->chunk_obstack); + = pp_token_list::make (buffer->m_chunk_obstack); if (ISDIGIT (*p)) { @@ -1695,7 +1713,7 @@ pretty_printer::format (text_info *text) formatters[argno] = &args[chunk++]; do { - obstack_1grow (&buffer->chunk_obstack, *p); + obstack_1grow (&buffer->m_chunk_obstack, *p); p++; } while (strchr ("qwlzt+#", p[-1])); @@ -1708,7 +1726,7 @@ pretty_printer::format (text_info *text) { do { - obstack_1grow (&buffer->chunk_obstack, *p); + obstack_1grow (&buffer->m_chunk_obstack, *p); p++; } while (ISDIGIT (p[-1])); @@ -1717,7 +1735,7 @@ pretty_printer::format (text_info *text) else { gcc_assert (*p == '*'); - obstack_1grow (&buffer->chunk_obstack, '*'); + obstack_1grow (&buffer->m_chunk_obstack, '*'); p++; if (ISDIGIT (*p)) @@ -1739,34 +1757,34 @@ pretty_printer::format (text_info *text) curarg++; } gcc_assert (*p == 's'); - obstack_1grow (&buffer->chunk_obstack, 's'); + obstack_1grow (&buffer->m_chunk_obstack, 's'); p++; } } if (*p == '\0') { - push_back_any_text (cur_token_list, &buffer->chunk_obstack); + push_back_any_text (cur_token_list, &buffer->m_chunk_obstack); break; } - obstack_1grow (&buffer->chunk_obstack, '\0'); - push_back_any_text (cur_token_list, &buffer->chunk_obstack); + obstack_1grow (&buffer->m_chunk_obstack, '\0'); + push_back_any_text (cur_token_list, &buffer->m_chunk_obstack); /* Start a new token list for the next (non-formatted) text. */ gcc_assert (chunk < PP_NL_ARGMAX * 2); args[chunk++] = cur_token_list - = pp_token_list::make (buffer->chunk_obstack); + = pp_token_list::make (buffer->m_chunk_obstack); } - obstack_1grow (&buffer->chunk_obstack, '\0'); - push_back_any_text (cur_token_list, &buffer->chunk_obstack); + obstack_1grow (&buffer->m_chunk_obstack, '\0'); + push_back_any_text (cur_token_list, &buffer->m_chunk_obstack); gcc_assert (chunk < PP_NL_ARGMAX * 2); args[chunk] = nullptr; /* Set output to the argument obstack, and switch line-wrapping and prefixing off. */ - buffer->obstack = &buffer->chunk_obstack; - const int old_line_length = buffer->line_length; + buffer->m_obstack = &buffer->m_chunk_obstack; + const int old_line_length = buffer->m_line_length; const pp_wrapping_mode_t old_wrapping_mode = pp_set_verbatim_wrapping (this); /* Note that you can debug the state of the chunk arrays here using @@ -1799,7 +1817,7 @@ pretty_printer::format (text_info *text) /* Accumulate the value of the formatted text into here. */ pp_token_list *formatted_tok_list - = pp_token_list::make (buffer->chunk_obstack); + = pp_token_list::make (buffer->m_chunk_obstack); /* We do not attempt to enforce any ordering on the modifier characters. */ @@ -1851,7 +1869,7 @@ pretty_printer::format (text_info *text) if (quote) { - push_back_any_text (formatted_tok_list, &buffer->chunk_obstack); + push_back_any_text (formatted_tok_list, &buffer->m_chunk_obstack); formatted_tok_list->push_back<pp_token_begin_quote> (); } @@ -2037,11 +2055,11 @@ pretty_printer::format (text_info *text) if (quote) { - push_back_any_text (formatted_tok_list, &buffer->chunk_obstack); + push_back_any_text (formatted_tok_list, &buffer->m_chunk_obstack); formatted_tok_list->push_back<pp_token_end_quote> (); } - push_back_any_text (formatted_tok_list, &buffer->chunk_obstack); + push_back_any_text (formatted_tok_list, &buffer->m_chunk_obstack); delete *formatters[argno]; *formatters[argno] = formatted_tok_list; } @@ -2056,8 +2074,8 @@ pretty_printer::format (text_info *text) m_format_postprocessor->handle (this); /* Revert to normal obstack and wrapping mode. */ - buffer->obstack = &buffer->formatted_obstack; - buffer->line_length = old_line_length; + buffer->m_obstack = &buffer->m_formatted_obstack; + buffer->m_line_length = old_line_length; pp_wrapping_mode (this) = old_wrapping_mode; clear_state (); } @@ -2094,7 +2112,11 @@ struct auto_obstack obstack m_obstack; }; -/* Format of a message pointed to by TEXT. +/* Phase 3 of formatting a message (phases 1 and 2 done by pp_format). + + Pop a pp_formatted_chunks from chunk_obstack, collecting all the tokens from + phases 1 and 2 of formatting, and writing into text in formatted_obstack. + If URLIFIER is non-null then use it on any quoted text that was not handled in phases 1 or 2 to potentially add URLs. */ @@ -2103,14 +2125,14 @@ pp_output_formatted_text (pretty_printer *pp, const urlifier *urlifier) { output_buffer * const buffer = pp_buffer (pp); - gcc_assert (buffer->obstack == &buffer->formatted_obstack); + gcc_assert (buffer->m_obstack == &buffer->m_formatted_obstack); - chunk_info *chunk_array = buffer->cur_chunk_array; + pp_formatted_chunks *chunk_array = buffer->m_cur_formatted_chunks; pp_token_list * const *token_lists = chunk_array->get_token_lists (); { /* Consolidate into one token list. */ - pp_token_list tokens (buffer->chunk_obstack); + pp_token_list tokens (buffer->m_chunk_obstack); for (unsigned chunk = 0; token_lists[chunk]; chunk++) { tokens.push_back_list (std::move (*token_lists[chunk])); @@ -2132,12 +2154,12 @@ pp_output_formatted_text (pretty_printer *pp, default_token_printer (pp, tokens); /* Close the scope here to ensure that "tokens" above is fully cleared up - before popping the current chunk_info, since that latter will pop + before popping the current pp_formatted_chunks, since that latter will pop the chunk_obstack, and "tokens" may be using blocks within - the current chunk_info's chunk_obstack level. */ + the current pp_formatted_chunks's chunk_obstack level. */ } - chunk_array->pop_from_output_buffer (*buffer); + buffer->pop_formatted_chunks (); } /* Default implementation of token printing. */ @@ -2229,10 +2251,10 @@ void pp_flush (pretty_printer *pp) { pp->clear_state (); - if (!pp_buffer (pp)->flush_p) + if (!pp_buffer (pp)->m_flush_p) return; pp_write_text_to_stream (pp); - fflush (pp_buffer (pp)->stream); + fflush (pp_buffer (pp)->m_stream); } /* Flush the content of BUFFER onto the attached stream independently @@ -2242,7 +2264,7 @@ pp_really_flush (pretty_printer *pp) { pp->clear_state (); pp_write_text_to_stream (pp); - fflush (pp_buffer (pp)->stream); + fflush (pp_buffer (pp)->m_stream); } /* Sets the number of maximum characters per line PRETTY-PRINTER can @@ -2259,9 +2281,9 @@ pp_set_line_maximum_length (pretty_printer *pp, int length) void pp_clear_output_area (pretty_printer *pp) { - obstack_free (pp_buffer (pp)->obstack, - obstack_base (pp_buffer (pp)->obstack)); - pp_buffer (pp)->line_length = 0; + obstack_free (pp_buffer (pp)->m_obstack, + obstack_base (pp_buffer (pp)->m_obstack)); + pp_buffer (pp)->m_line_length = 0; } /* Set PREFIX for PRETTY-PRINTER, taking ownership of PREFIX, which @@ -2413,7 +2435,7 @@ void pp_append_text (pretty_printer *pp, const char *start, const char *end) { /* Emit prefix and skip whitespace if we're starting a new line. */ - if (pp_buffer (pp)->line_length == 0) + if (pp_buffer (pp)->m_line_length == 0) { pp->emit_prefix (); if (pp_is_wrapping_line (pp)) @@ -2444,7 +2466,7 @@ pp_last_position_in_text (const pretty_printer *pp) int pretty_printer::remaining_character_count_for_line () { - return m_maximum_length - pp_buffer (this)->line_length; + return m_maximum_length - pp_buffer (this)->m_line_length; } /* Format a message into BUFFER a la printf. */ @@ -2479,9 +2501,9 @@ pp_verbatim (pretty_printer *pp, const char *msg, ...) void pp_newline (pretty_printer *pp) { - obstack_1grow (pp_buffer (pp)->obstack, '\n'); + obstack_1grow (pp_buffer (pp)->m_obstack, '\n'); pp_needs_newline (pp) = false; - pp_buffer (pp)->line_length = 0; + pp_buffer (pp)->m_line_length = 0; } /* Have PRETTY-PRINTER add a CHARACTER. */ @@ -2497,8 +2519,8 @@ pp_character (pretty_printer *pp, int c) if (ISSPACE (c)) return; } - obstack_1grow (pp_buffer (pp)->obstack, c); - ++pp_buffer (pp)->line_length; + obstack_1grow (pp_buffer (pp)->m_obstack, c); + ++pp_buffer (pp)->m_line_length; } /* Append a STRING to the output area of PRETTY-PRINTER; the STRING may @@ -3018,7 +3040,7 @@ pp_markup::context::end_highlight_color () void pp_markup::context::push_back_any_text () { - obstack *cur_obstack = m_buf.obstack; + obstack *cur_obstack = m_buf.m_obstack; obstack_1grow (cur_obstack, '\0'); m_formatted_token_list->push_back_text (label_text::borrow (XOBFINISH (cur_obstack, diff --git a/gcc/pretty-print.h b/gcc/pretty-print.h index e0505b2683c2..14a6c53a4ac0 100644 --- a/gcc/pretty-print.h +++ b/gcc/pretty-print.h @@ -69,7 +69,7 @@ enum diagnostic_prefixing_rule_t DIAGNOSTICS_SHOW_PREFIX_EVERY_LINE = 0x2 }; -class chunk_info; +class pp_formatted_chunks; class output_buffer; class pp_token_list; class urlifier; @@ -84,36 +84,44 @@ class output_buffer { public: output_buffer (); + output_buffer (const output_buffer &) = delete; + output_buffer (output_buffer &&) = delete; ~output_buffer (); + output_buffer & operator= (const output_buffer &) = delete; + output_buffer & operator= (output_buffer &&) = delete; + + pp_formatted_chunks *push_formatted_chunks (); + void pop_formatted_chunks (); /* Obstack where the text is built up. */ - struct obstack formatted_obstack; + struct obstack m_formatted_obstack; /* Obstack containing a chunked representation of the format specification plus arguments. */ - struct obstack chunk_obstack; + struct obstack m_chunk_obstack; /* Currently active obstack: one of the above two. This is used so that the text formatters don't need to know which phase we're in. */ - struct obstack *obstack; + struct obstack *m_obstack; - /* Stack of chunk arrays. These come from the chunk_obstack. */ - chunk_info *cur_chunk_array; + /* Topmost element in a stack of arrays of formatted chunks. + These come from the chunk_obstack. */ + pp_formatted_chunks *m_cur_formatted_chunks; /* Where to output formatted text. */ - FILE *stream; + FILE *m_stream; /* The amount of characters output so far. */ - int line_length; + int m_line_length; /* This must be large enough to hold any printed integer or floating-point value. */ - char digit_buffer[128]; + char m_digit_buffer[128]; /* Nonzero means that text should be flushed when appropriate. Otherwise, text is buffered until either pp_really_flush or pp_clear_output_area are called. */ - bool flush_p; + bool m_flush_p; }; /* Finishes constructing a NULL-terminated character string representing @@ -121,8 +129,8 @@ public: inline const char * output_buffer_formatted_text (output_buffer *buff) { - obstack_1grow (buff->obstack, '\0'); - return (const char *) obstack_base (buff->obstack); + obstack_1grow (buff->m_obstack, '\0'); + return (const char *) obstack_base (buff->m_obstack); } /* Append to the output buffer a string specified by its @@ -131,12 +139,12 @@ inline void output_buffer_append_r (output_buffer *buff, const char *start, int length) { gcc_checking_assert (start); - obstack_grow (buff->obstack, start, length); + obstack_grow (buff->m_obstack, start, length); for (int i = 0; i < length; i++) if (start[i] == '\n') - buff->line_length = 0; + buff->m_line_length = 0; else - buff->line_length++; + buff->m_line_length++; } /* Return a pointer to the last character emitted in the @@ -145,7 +153,7 @@ inline const char * output_buffer_last_position_in_text (const output_buffer *buff) { const char *p = NULL; - struct obstack *text = buff->obstack; + struct obstack *text = buff->m_obstack; if (obstack_base (text) != obstack_next_free (text)) p = ((const char *) obstack_next_free (text)) - 1; @@ -262,7 +270,7 @@ public: void set_output_stream (FILE *outfile) { - m_buffer->stream = outfile; + m_buffer->m_stream = outfile; } void set_token_printer (token_printer* tp) @@ -508,8 +516,8 @@ pp_wrapping_mode (pretty_printer *pp) #define pp_scalar(PP, FORMAT, SCALAR) \ do \ { \ - sprintf (pp_buffer (PP)->digit_buffer, FORMAT, SCALAR); \ - pp_string (PP, pp_buffer (PP)->digit_buffer); \ + sprintf (pp_buffer (PP)->m_digit_buffer, FORMAT, SCALAR); \ + pp_string (PP, pp_buffer (PP)->m_digit_buffer); \ } \ while (0) #define pp_decimal_int(PP, I) pp_scalar (PP, "%d", I) @@ -632,12 +640,12 @@ pp_wide_int (pretty_printer *pp, const wide_int_ref &w, signop sgn) { unsigned int len; print_dec_buf_size (w, sgn, &len); - if (UNLIKELY (len > sizeof (pp_buffer (pp)->digit_buffer))) + if (UNLIKELY (len > sizeof (pp_buffer (pp)->m_digit_buffer))) pp_wide_int_large (pp, w, sgn); else { - print_dec (w, pp_buffer (pp)->digit_buffer, sgn); - pp_string (pp, pp_buffer (pp)->digit_buffer); + print_dec (w, pp_buffer (pp)->m_digit_buffer, sgn); + pp_string (pp, pp_buffer (pp)->m_digit_buffer); } } diff --git a/gcc/tree-pretty-print.cc b/gcc/tree-pretty-print.cc index 4bb946bb0e83..b378ffbfb4ca 100644 --- a/gcc/tree-pretty-print.cc +++ b/gcc/tree-pretty-print.cc @@ -2401,7 +2401,7 @@ dump_generic_node (pretty_printer *pp, tree node, int spc, dump_flags_t flags, } unsigned int len; print_hex_buf_size (val, &len); - if (UNLIKELY (len > sizeof (pp_buffer (pp)->digit_buffer))) + if (UNLIKELY (len > sizeof (pp_buffer (pp)->m_digit_buffer))) { char *buf = XALLOCAVEC (char, len); print_hex (val, buf); @@ -2409,8 +2409,8 @@ dump_generic_node (pretty_printer *pp, tree node, int spc, dump_flags_t flags, } else { - print_hex (val, pp_buffer (pp)->digit_buffer); - pp_string (pp, pp_buffer (pp)->digit_buffer); + print_hex (val, pp_buffer (pp)->m_digit_buffer); + pp_string (pp, pp_buffer (pp)->m_digit_buffer); } } if ((flags & TDF_GIMPLE) @@ -4898,10 +4898,10 @@ pp_double_int (pretty_printer *pp, double_int d, bool uns) } /* Would "%x%0*x" or "%x%*0x" get zero-padding on all systems? */ - sprintf (pp_buffer (pp)->digit_buffer, + sprintf (pp_buffer (pp)->m_digit_buffer, HOST_WIDE_INT_PRINT_DOUBLE_HEX, (unsigned HOST_WIDE_INT) high, low); - pp_string (pp, pp_buffer (pp)->digit_buffer); + pp_string (pp, pp_buffer (pp)->m_digit_buffer); } } -- GitLab