Output DW_AT_entry_pc based on markers.
Introduce DW_AT_GNU_entry_view as a DWARF extension.
If views are enabled are we're not in strict compliance mode, output
DW_AT_GNU_entry_view if it might be nonzero.
This patch depends on SFN and LVU patchsets, and on the IEPM patch that
introduces the inline_entry debug hook.
for include/ChangeLog
* dwarf2.def (DW_AT_GNU_entry_view): New.
for gcc/ChangeLog
* cfgexpand.c (expand_gimple_basic_block): Handle inline entry
markers.
* dwarf2out.c (dwarf2_debug_hooks): Enable inline_entry hook.
(BLOCK_INLINE_ENTRY_LABEL): New.
(dwarf2out_var_location): Disregard inline entry markers.
(inline_entry_data): New struct.
(inline_entry_data_hasher): New hashtable type.
(inline_entry_data_hasher::hash): New.
(inline_entry_data_hasher::equal): New.
(inline_entry_data_table): New variable.
(add_high_low_attributes): Add DW_AT_entry_pc and
DW_AT_GNU_entry_view attributes if a pending entry is found
in inline_entry_data_table. Add old entry_pc attribute only
if debug nonbinding markers are disabled.
(gen_inlined_subroutine_die): Set BLOCK_DIE if nonbinding
markers are enabled.
(block_within_block_p, dwarf2out_inline_entry): New.
(dwarf2out_finish): Check that no entries remained in
inline_entry_data_table.
* final.c (reemit_insn_block_notes): Handle inline entry notes.
(final_scan_insn, notice_source_line): Likewise.
(rest_of_clean_state): Skip inline entry markers.
* gimple-pretty-print.c (dump_gimple_debug): Handle inline entry
markers.
* gimple.c (gimple_build_debug_inline_entry): New.
* gimple.h (enum gimple_debug_subcode): Add
GIMPLE_DEBUG_INLINE_ENTRY.
(gimple_build_debug_inline_entry): Declare.
(gimple_debug_inline_entry_p): New.
(gimple_debug_nonbind_marker_p): Adjust.
* insn-notes.def (INLINE_ENTRY): New.
* print-rtl.c (rtx_writer::print_rtx_operand_code_0): Handle
inline entry marker notes.
(print_insn): Likewise.
* rtl.h (NOTE_MARKER_P): Add INLINE_ENTRY support.
(INSN_DEBUG_MARKER_KIND): Likewise.
(GEN_RTX_DEBUG_MARKER_INLINE_ENTRY_PAT): New.
* tree-inline.c (expand_call_inline): Build and insert
debug_inline_entry stmt.
* tree-ssa-live.c (remove_unused_scope_block_p): Preserve
inline entry blocks early, if nonbind markers are enabled.
(dump_scope_block): Dump fragment info.
* var-tracking.c (reemit_marker_as_note): Handle inline entry note.
* doc/gimple.texi (gimple_debug_inline_entry_p): New.
(gimple_build_debug_inline_entry): New.
* doc/invoke.texi (gstatement-frontiers, gno-statement-frontiers):
Enable/disable inline entry points too.
* doc/rtl.texi (NOTE_INSN_INLINE_ENTRY): New.
(DEBUG_INSN): Describe inline entry markers.
From-SVN: r257511
2018-02-09 Alexandre Oliva <aoliva@redhat.com>
+ * cfgexpand.c (expand_gimple_basic_block): Handle inline entry
+ markers.
+ * dwarf2out.c (dwarf2_debug_hooks): Enable inline_entry hook.
+ (BLOCK_INLINE_ENTRY_LABEL): New.
+ (dwarf2out_var_location): Disregard inline entry markers.
+ (inline_entry_data): New struct.
+ (inline_entry_data_hasher): New hashtable type.
+ (inline_entry_data_hasher::hash): New.
+ (inline_entry_data_hasher::equal): New.
+ (inline_entry_data_table): New variable.
+ (add_high_low_attributes): Add DW_AT_entry_pc and
+ DW_AT_GNU_entry_view attributes if a pending entry is found
+ in inline_entry_data_table. Add old entry_pc attribute only
+ if debug nonbinding markers are disabled.
+ (gen_inlined_subroutine_die): Set BLOCK_DIE if nonbinding
+ markers are enabled.
+ (block_within_block_p, dwarf2out_inline_entry): New.
+ (dwarf2out_finish): Check that no entries remained in
+ inline_entry_data_table.
+ * final.c (reemit_insn_block_notes): Handle inline entry notes.
+ (final_scan_insn, notice_source_line): Likewise.
+ (rest_of_clean_state): Skip inline entry markers.
+ * gimple-pretty-print.c (dump_gimple_debug): Handle inline entry
+ markers.
+ * gimple.c (gimple_build_debug_inline_entry): New.
+ * gimple.h (enum gimple_debug_subcode): Add
+ GIMPLE_DEBUG_INLINE_ENTRY.
+ (gimple_build_debug_inline_entry): Declare.
+ (gimple_debug_inline_entry_p): New.
+ (gimple_debug_nonbind_marker_p): Adjust.
+ * insn-notes.def (INLINE_ENTRY): New.
+ * print-rtl.c (rtx_writer::print_rtx_operand_code_0): Handle
+ inline entry marker notes.
+ (print_insn): Likewise.
+ * rtl.h (NOTE_MARKER_P): Add INLINE_ENTRY support.
+ (INSN_DEBUG_MARKER_KIND): Likewise.
+ (GEN_RTX_DEBUG_MARKER_INLINE_ENTRY_PAT): New.
+ * tree-inline.c (expand_call_inline): Build and insert
+ debug_inline_entry stmt.
+ * tree-ssa-live.c (remove_unused_scope_block_p): Preserve
+ inline entry blocks early, if nonbind markers are enabled.
+ (dump_scope_block): Dump fragment info.
+ * var-tracking.c (reemit_marker_as_note): Handle inline entry note.
+ * doc/gimple.texi (gimple_debug_inline_entry_p): New.
+ (gimple_build_debug_inline_entry): New.
+ * doc/invoke.texi (gstatement-frontiers, gno-statement-frontiers):
+ Enable/disable inline entry points too.
+ * doc/rtl.texi (NOTE_INSN_INLINE_ENTRY): New.
+ (DEBUG_INSN): Describe inline entry markers.
+
* common.opt (gvariable-location-views): New.
(gvariable-location-views=incompat5): New.
* config.in: Rebuilt.
goto delink_debug_stmt;
else if (gimple_debug_begin_stmt_p (stmt))
val = GEN_RTX_DEBUG_MARKER_BEGIN_STMT_PAT ();
+ else if (gimple_debug_inline_entry_p (stmt))
+ {
+ tree block = gimple_block (stmt);
+
+ if (block)
+ val = GEN_RTX_DEBUG_MARKER_INLINE_ENTRY_PAT ();
+ else
+ goto delink_debug_stmt;
+ }
else
gcc_unreachable ();
a source statement.
@end deftypefn
+@deftypefn {GIMPLE function} gimple_debug_inline_entry_p (gimple g)
+Return true if g is a @code{GIMPLE_DEBUG} that marks the entry
+point of an inlined function.
+@end deftypefn
+
@deftypefn {GIMPLE function} gimple_debug_nonbind_marker_p (gimple g)
Return true if g is a @code{GIMPLE_DEBUG} that marks a program location,
without any variable binding.
@cindex @code{GIMPLE_DEBUG}
@cindex @code{GIMPLE_DEBUG_BIND}
@cindex @code{GIMPLE_DEBUG_BEGIN_STMT}
+@cindex @code{GIMPLE_DEBUG_INLINE_ENTRY}
@deftypefn {GIMPLE function} gdebug *gimple_build_debug_bind (tree var, @
tree value, gimple stmt)
statements are.
@end deftypefn
+@deftypefn {GIMPLE function} gimple gimple_build_debug_inline_entry (tree block, location_t location)
+Build a @code{GIMPLE_DEBUG} statement with
+@code{GIMPLE_DEBUG_INLINE_ENTRY} @code{subcode}. The effect of this
+statement is to tell debug information generation machinery that a
+function call at @code{location} underwent inline substitution, that
+@code{block} is the enclosing lexical block created for the
+substitution, and that at the point of the program in which the stmt is
+inserted, all parameters for the inlined function are bound to the
+respective arguments, and none of the side effects of its stmts are
+observable.
+@end deftypefn
+
@node @code{GIMPLE_EH_FILTER}
@subsection @code{GIMPLE_EH_FILTER}
@cindex @code{GIMPLE_EH_FILTER}
@item (debug_marker:@var{mode})
Marks a program location. With @code{VOIDmode}, it stands for the
beginning of a statement, a recommended inspection point logically after
-all prior side effects, and before any subsequent side effects.
+all prior side effects, and before any subsequent side effects. With
+@code{BLKmode}, it indicates an inline entry point: the lexical block
+encoded in the @code{INSN_LOCATION} is the enclosing block that encloses
+the inlined function.
@end table
debuggign information. It indicates the beginning of a user
statement.
+@findex NOTE_INSN_INLINE_ENTRY
+@item NOTE_INSN_INLINE_ENTRY
+This note is used to generate @code{entry_pc} for inlined subroutines in
+debugging information. It indicates an inspection point at which all
+arguments for the inlined function have been bound, and before its first
+statement.
+
@end table
These codes are printed symbolically when they appear in debugging dumps.
it stands for the value bound to the corresponding
@code{DEBUG_EXPR_DECL}.
-@code{GIMPLE_DEBUG_BEGIN_STMT} is expanded to RTL as a @code{DEBUG_INSN}
-with a @code{VOIDmode} @code{DEBUG_MARKER} @code{PATTERN}. These
+@code{GIMPLE_DEBUG_BEGIN_STMT} and @code{GIMPLE_DEBUG_INLINE_ENTRY} are
+expanded to RTL as a @code{DEBUG_INSN} with a @code{DEBUG_MARKER}
+@code{PATTERN}; the difference is the RTL mode: the former's
+@code{DEBUG_MARKER} is @code{VOIDmode}, whereas the latter is
+@code{BLKmode}; information about the inlined function can be taken from
+the lexical block encoded in the @code{INSN_LOCATION}. These
@code{DEBUG_INSN}s, that do not carry @code{VAR_LOCATION} information,
just @code{DEBUG_MARKER}s, can be detected by testing
@code{DEBUG_MARKER_INSN_P}, whereas those that do can be recognized as
information is kept in pseudo-instruction form, so that, unlike notes,
it gets the same treatment and adjustments that regular instructions
would. It is the variable tracking pass that turns these
-pseudo-instructions into @code{NOTE_INSN_VAR_LOCATION} and
-@code{NOTE_INSN_BEGIN_STMT} notes,
+pseudo-instructions into @code{NOTE_INSN_VAR_LOCATION},
+@code{NOTE_INSN_BEGIN_STMT} and @code{NOTE_INSN_INLINE_ENTRY} notes,
analyzing control flow, value equivalences and changes to registers and
memory referenced in value expressions, propagating the values of debug
temporaries and determining expressions that can be used to compute the
dw_die_ref);
static void dwarf2out_abstract_function (tree);
static void dwarf2out_var_location (rtx_insn *);
+static void dwarf2out_inline_entry (tree);
static void dwarf2out_size_function (tree);
static void dwarf2out_begin_function (tree);
static void dwarf2out_end_function (unsigned int);
debug_nothing_rtx_code_label, /* label */
debug_nothing_int, /* handle_pch */
dwarf2out_var_location,
- debug_nothing_tree, /* inline_entry */
+ dwarf2out_inline_entry, /* inline_entry */
dwarf2out_size_function, /* size_function */
dwarf2out_switch_text_section,
dwarf2out_set_name,
#ifndef BLOCK_BEGIN_LABEL
#define BLOCK_BEGIN_LABEL "LBB"
#endif
+#ifndef BLOCK_INLINE_ENTRY_LABEL
+#define BLOCK_INLINE_ENTRY_LABEL "LBI"
+#endif
#ifndef BLOCK_END_LABEL
#define BLOCK_END_LABEL "LBE"
#endif
return x->decl_id == y->decl_id && x->die_parent == y->die_parent;
}
+/* Hold information about markers for inlined entry points. */
+struct GTY ((for_user)) inline_entry_data
+{
+ /* The block that's the inlined_function_outer_scope for an inlined
+ function. */
+ tree block;
+
+ /* The label at the inlined entry point. */
+ const char *label_pfx;
+ unsigned int label_num;
+
+ /* The view number to be used as the inlined entry point. */
+ var_loc_view view;
+};
+
+struct inline_entry_data_hasher : ggc_ptr_hash <inline_entry_data>
+{
+ typedef tree compare_type;
+ static inline hashval_t hash (const inline_entry_data *);
+ static inline bool equal (const inline_entry_data *, const_tree);
+};
+
+/* Hash table routines for inline_entry_data. */
+
+inline hashval_t
+inline_entry_data_hasher::hash (const inline_entry_data *data)
+{
+ return htab_hash_pointer (data->block);
+}
+
+inline bool
+inline_entry_data_hasher::equal (const inline_entry_data *data,
+ const_tree block)
+{
+ return data->block == block;
+}
+
+/* Inlined entry points pending DIE creation in this compilation unit. */
+
+static GTY(()) hash_table<inline_entry_data_hasher> *inline_entry_data_table;
+
+
/* Return TRUE if DECL, which may have been previously generated as
OLD_DIE, is a candidate for a DW_AT_specification. DECLARATION is
true if decl (or its origin) is either an extern declaration or a
{
char label[MAX_ARTIFICIAL_LABEL_BYTES];
+ if (inline_entry_data **iedp
+ = !inline_entry_data_table ? NULL
+ : inline_entry_data_table->find_slot_with_hash (stmt,
+ htab_hash_pointer (stmt),
+ NO_INSERT))
+ {
+ inline_entry_data *ied = *iedp;
+ gcc_assert (MAY_HAVE_DEBUG_MARKER_INSNS);
+ gcc_assert (inlined_function_outer_scope_p (stmt));
+ ASM_GENERATE_INTERNAL_LABEL (label, ied->label_pfx, ied->label_num);
+ add_AT_lbl_id (die, DW_AT_entry_pc, label);
+
+ if (debug_variable_location_views && !ZERO_VIEW_P (ied->view))
+ {
+ if (!output_asm_line_debug_info ())
+ add_AT_unsigned (die, DW_AT_GNU_entry_view, ied->view);
+ else
+ {
+ ASM_GENERATE_INTERNAL_LABEL (label, "LVU", ied->view);
+ /* FIXME: this will resolve to a small number. Could we
+ possibly emit smaller data? Ideally we'd emit a
+ uleb128, but that would make the size of DIEs
+ impossible for the compiler to compute, since it's
+ the assembler that computes the value of the view
+ label in this case. Ideally, we'd have a single form
+ encompassing both the address and the view, and
+ indirecting them through a table might make things
+ easier, but even that would be more wasteful,
+ space-wise, than what we have now. */
+ add_AT_lbl_id (die, DW_AT_GNU_entry_view, label);
+ }
+ }
+
+ inline_entry_data_table->clear_slot (iedp);
+ }
+
if (BLOCK_FRAGMENT_CHAIN (stmt)
&& (dwarf_version >= 3 || !dwarf_strict))
{
dw_die_ref pdie;
dw_attr_node *attr = NULL;
- if (inlined_function_outer_scope_p (stmt))
+ if (!MAY_HAVE_DEBUG_MARKER_INSNS && inlined_function_outer_scope_p (stmt))
{
ASM_GENERATE_INTERNAL_LABEL (label, BLOCK_BEGIN_LABEL,
BLOCK_NUMBER (stmt));
dw_die_ref subr_die
= new_die (DW_TAG_inlined_subroutine, context_die, stmt);
- if (call_arg_locations)
+ if (call_arg_locations || MAY_HAVE_DEBUG_MARKER_INSNS)
BLOCK_DIE (stmt) = subr_die;
add_abstract_origin_attribute (subr_die, decl);
if (TREE_ASM_WRITTEN (stmt))
|| ! NOTE_P (next_note)
|| (NOTE_KIND (next_note) != NOTE_INSN_VAR_LOCATION
&& NOTE_KIND (next_note) != NOTE_INSN_BEGIN_STMT
+ && NOTE_KIND (next_note) != NOTE_INSN_INLINE_ENTRY
&& NOTE_KIND (next_note) != NOTE_INSN_CALL_ARG_LOCATION))
next_note = NULL;
last_in_cold_section_p = in_cold_section_p;
}
+/* Check whether BLOCK, a lexical block, is nested within OUTER, or is
+ OUTER itself. If BOTHWAYS, check not only that BLOCK can reach
+ OUTER through BLOCK_SUPERCONTEXT links, but also that there is a
+ path from OUTER to BLOCK through BLOCK_SUBBLOCKs and
+ BLOCK_FRAGMENT_ORIGIN links. */
+static bool
+block_within_block_p (tree block, tree outer, bool bothways)
+{
+ if (block == outer)
+ return true;
+
+ /* Quickly check that OUTER is up BLOCK's supercontext chain. */
+ for (tree context = BLOCK_SUPERCONTEXT (block);
+ context != outer;
+ context = BLOCK_SUPERCONTEXT (context))
+ if (!context || TREE_CODE (context) != BLOCK)
+ return false;
+
+ if (!bothways)
+ return true;
+
+ /* Now check that each block is actually referenced by its
+ parent. */
+ for (tree context = BLOCK_SUPERCONTEXT (block); ;
+ context = BLOCK_SUPERCONTEXT (context))
+ {
+ if (BLOCK_FRAGMENT_ORIGIN (context))
+ {
+ gcc_assert (!BLOCK_SUBBLOCKS (context));
+ context = BLOCK_FRAGMENT_ORIGIN (context);
+ }
+ for (tree sub = BLOCK_SUBBLOCKS (context);
+ sub != block;
+ sub = BLOCK_CHAIN (sub))
+ if (!sub)
+ return false;
+ if (context == outer)
+ return true;
+ else
+ block = context;
+ }
+}
+
+/* Called during final while assembling the marker of the entry point
+ for an inlined function. */
+
+static void
+dwarf2out_inline_entry (tree block)
+{
+ /* If we can't represent it, don't bother. */
+ if (!(dwarf_version >= 3 || !dwarf_strict))
+ return;
+
+ gcc_assert (DECL_P (block_ultimate_origin (block)));
+
+ /* Sanity check the block tree. This would catch a case in which
+ BLOCK got removed from the tree reachable from the outermost
+ lexical block, but got retained in markers. It would still link
+ back to its parents, but some ancestor would be missing a link
+ down the path to the sub BLOCK. If the block got removed, its
+ BLOCK_NUMBER will not be a usable value. */
+ if (flag_checking)
+ gcc_assert (block_within_block_p (block,
+ DECL_INITIAL (current_function_decl),
+ true));
+
+ gcc_assert (inlined_function_outer_scope_p (block));
+ gcc_assert (!BLOCK_DIE (block));
+
+ if (BLOCK_FRAGMENT_ORIGIN (block))
+ block = BLOCK_FRAGMENT_ORIGIN (block);
+ /* Can the entry point ever not be at the beginning of an
+ unfragmented lexical block? */
+ else if (!(BLOCK_FRAGMENT_CHAIN (block)
+ || (cur_line_info_table
+ && !ZERO_VIEW_P (cur_line_info_table->view))))
+ return;
+
+ if (!inline_entry_data_table)
+ inline_entry_data_table
+ = hash_table<inline_entry_data_hasher>::create_ggc (10);
+
+
+ inline_entry_data **iedp
+ = inline_entry_data_table->find_slot_with_hash (block,
+ htab_hash_pointer (block),
+ INSERT);
+ if (*iedp)
+ /* ??? Ideally, we'd record all entry points for the same inlined
+ function (some may have been duplicated by e.g. unrolling), but
+ we have no way to represent that ATM. */
+ return;
+
+ inline_entry_data *ied = *iedp = ggc_cleared_alloc<inline_entry_data> ();
+ ied->block = block;
+ ied->label_pfx = BLOCK_INLINE_ENTRY_LABEL;
+ ied->label_num = BLOCK_NUMBER (block);
+ if (cur_line_info_table)
+ ied->view = cur_line_info_table->view;
+
+ char label[MAX_ARTIFICIAL_LABEL_BYTES];
+
+ ASM_GENERATE_INTERNAL_LABEL (label, BLOCK_INLINE_ENTRY_LABEL,
+ BLOCK_NUMBER (block));
+ ASM_OUTPUT_LABEL (asm_out_file, label);
+}
+
/* Called from finalize_size_functions for size functions so that their body
can be encoded in the debug info to describe the layout of variable-length
structures. */
/* Flush out any latecomers to the limbo party. */
flush_limbo_die_list ();
+ if (inline_entry_data_table)
+ gcc_assert (inline_entry_data_table->elements () == 0);
+
if (flag_checking)
{
verify_die (comp_unit_die ());
break;
case NOTE_INSN_BEGIN_STMT:
+ case NOTE_INSN_INLINE_ENTRY:
this_block = LOCATION_BLOCK (NOTE_MARKER_LOCATION (insn));
goto set_cur_block_to_this_block;
if (!DECL_IGNORED_P (current_function_decl)
&& notice_source_line (insn, NULL))
{
+ output_source_line:
(*debug_hooks->source_line) (last_linenum, last_columnnum,
last_filename, last_discriminator,
true);
}
break;
+ case NOTE_INSN_INLINE_ENTRY:
+ gcc_checking_assert (cfun->debug_nonbind_markers);
+ if (!DECL_IGNORED_P (current_function_decl))
+ {
+ if (!notice_source_line (insn, NULL))
+ break;
+ (*debug_hooks->inline_entry) (LOCATION_BLOCK
+ (NOTE_MARKER_LOCATION (insn)));
+ goto output_source_line;
+ }
+ break;
+
default:
gcc_unreachable ();
break;
if (NOTE_MARKER_P (insn))
{
location_t loc = NOTE_MARKER_LOCATION (insn);
+ /* The inline entry markers (gimple, insn, note) carry the
+ location of the call, because that's what we want to carry
+ during compilation, but the location we want to output in
+ debug information for the inline entry point is the location
+ of the function itself. */
+ if (NOTE_KIND (insn) == NOTE_INSN_INLINE_ENTRY)
+ {
+ tree block = LOCATION_BLOCK (loc);
+ tree fn = block_ultimate_origin (block);
+ loc = DECL_SOURCE_LOCATION (fn);
+ }
expanded_location xloc = expand_location (loc);
if (xloc.line == 0)
{
&& (!NOTE_P (insn) ||
(NOTE_KIND (insn) != NOTE_INSN_VAR_LOCATION
&& NOTE_KIND (insn) != NOTE_INSN_BEGIN_STMT
+ && NOTE_KIND (insn) != NOTE_INSN_INLINE_ENTRY
&& NOTE_KIND (insn) != NOTE_INSN_CALL_ARG_LOCATION
&& NOTE_KIND (insn) != NOTE_INSN_BLOCK_BEG
&& NOTE_KIND (insn) != NOTE_INSN_BLOCK_END
dump_gimple_fmt (buffer, spc, flags, "# DEBUG BEGIN_STMT");
break;
+ case GIMPLE_DEBUG_INLINE_ENTRY:
+ if (flags & TDF_RAW)
+ dump_gimple_fmt (buffer, spc, flags, "%G INLINE_ENTRY %T", gs,
+ gimple_block (gs)
+ ? block_ultimate_origin (gimple_block (gs))
+ : NULL_TREE);
+ else
+ dump_gimple_fmt (buffer, spc, flags, "# DEBUG INLINE_ENTRY %T",
+ gimple_block (gs)
+ ? block_ultimate_origin (gimple_block (gs))
+ : NULL_TREE);
+ break;
+
default:
gcc_unreachable ();
}
}
+/* Build a new GIMPLE_DEBUG_INLINE_ENTRY statement in BLOCK at
+ LOCATION. The BLOCK links to the inlined function. */
+
+gdebug *
+gimple_build_debug_inline_entry (tree block, location_t location
+ MEM_STAT_DECL)
+{
+ gdebug *p
+ = as_a <gdebug *> (
+ gimple_build_with_ops_stat (GIMPLE_DEBUG,
+ (unsigned)GIMPLE_DEBUG_INLINE_ENTRY, 0
+ PASS_MEM_STAT));
+
+ gimple_set_location (p, location);
+ gimple_set_block (p, block);
+ cfun->debug_marker_count++;
+
+ return p;
+}
+
+
/* Build a GIMPLE_OMP_CRITICAL statement.
BODY is the sequence of statements for which only one thread can execute.
enum gimple_debug_subcode {
GIMPLE_DEBUG_BIND = 0,
GIMPLE_DEBUG_SOURCE_BIND = 1,
- GIMPLE_DEBUG_BEGIN_STMT = 2
+ GIMPLE_DEBUG_BEGIN_STMT = 2,
+ GIMPLE_DEBUG_INLINE_ENTRY = 3
};
/* Masks for selecting a pass local flag (PLF) to work on. These
gdebug *gimple_build_debug_bind (tree, tree, gimple * CXX_MEM_STAT_INFO);
gdebug *gimple_build_debug_source_bind (tree, tree, gimple * CXX_MEM_STAT_INFO);
gdebug *gimple_build_debug_begin_stmt (tree, location_t CXX_MEM_STAT_INFO);
+gdebug *gimple_build_debug_inline_entry (tree, location_t CXX_MEM_STAT_INFO);
gomp_critical *gimple_build_omp_critical (gimple_seq, tree, tree);
gomp_for *gimple_build_omp_for (gimple_seq, int, tree, size_t, gimple_seq);
gomp_parallel *gimple_build_omp_parallel (gimple_seq, tree, tree, tree);
return false;
}
+/* Return true if S is a GIMPLE_DEBUG INLINE_ENTRY statement. */
+
+static inline bool
+gimple_debug_inline_entry_p (const gimple *s)
+{
+ if (is_gimple_debug (s))
+ return s->subcode == GIMPLE_DEBUG_INLINE_ENTRY;
+
+ return false;
+}
+
/* Return true if S is a GIMPLE_DEBUG non-binding marker statement. */
static inline bool
gimple_debug_nonbind_marker_p (const gimple *s)
{
if (is_gimple_debug (s))
- return s->subcode == GIMPLE_DEBUG_BEGIN_STMT;
+ return s->subcode == GIMPLE_DEBUG_BEGIN_STMT
+ || s->subcode == GIMPLE_DEBUG_INLINE_ENTRY;
return false;
}
/* The beginning of a statement. */
INSN_NOTE (BEGIN_STMT)
+/* The entry point for an inlined function. Its NOTE_BLOCK references
+ the lexical block whose abstract origin is the inlined function. */
+INSN_NOTE (INLINE_ENTRY)
+
/* Record the struct for the following basic block. Uses
NOTE_BASIC_BLOCK. FIXME: Redundant with the basic block pointer
now included in every insn. NOTE: If there's no CFG anymore, in other words,
break;
case NOTE_INSN_BEGIN_STMT:
+ case NOTE_INSN_INLINE_ENTRY:
#ifndef GENERATOR_FILE
{
expanded_location xloc
pp_string (pp, "debug begin stmt marker");
break;
+ case NOTE_INSN_INLINE_ENTRY:
+ pp_string (pp, "debug inline entry marker");
+ break;
+
default:
gcc_unreachable ();
}
for which NOTE_MARKER_LOCATION can be used. */
#define NOTE_MARKER_P(INSN) \
(NOTE_P (INSN) && \
- (NOTE_KIND (INSN) == NOTE_INSN_BEGIN_STMT))
+ (NOTE_KIND (INSN) == NOTE_INSN_BEGIN_STMT \
+ || NOTE_KIND (INSN) == NOTE_INSN_INLINE_ENTRY))
/* Variable declaration and the location of a variable. */
#define PAT_VAR_LOCATION_DECL(PAT) (XCTREE ((PAT), 0, VAR_LOCATION))
(GET_CODE (PATTERN (INSN)) == DEBUG_MARKER \
? (GET_MODE (PATTERN (INSN)) == VOIDmode \
? NOTE_INSN_BEGIN_STMT \
+ : GET_MODE (PATTERN (INSN)) == BLKmode \
+ ? NOTE_INSN_INLINE_ENTRY \
: (enum insn_note)-1) \
: (enum insn_note)-1)
/* Create patterns for debug markers. These and the above abstract
wouldn't be a problem. */
#define GEN_RTX_DEBUG_MARKER_BEGIN_STMT_PAT() \
gen_rtx_DEBUG_MARKER (VOIDmode)
+#define GEN_RTX_DEBUG_MARKER_INLINE_ENTRY_PAT() \
+ gen_rtx_DEBUG_MARKER (BLKmode)
/* The VAR_LOCATION rtx in a DEBUG_INSN. */
#define INSN_VAR_LOCATION(INSN) \
GSI_NEW_STMT);
}
initialize_inlined_parameters (id, stmt, fn, bb);
+ if (debug_nonbind_markers_p && id->block
+ && inlined_function_outer_scope_p (id->block))
+ {
+ gimple_stmt_iterator si = gsi_last_bb (bb);
+ gsi_insert_after (&si, gimple_build_debug_inline_entry
+ (id->block, input_location), GSI_NEW_STMT);
+ }
if (DECL_INITIAL (fn))
{
else if (!BLOCK_SUPERCONTEXT (scope)
|| TREE_CODE (BLOCK_SUPERCONTEXT (scope)) == FUNCTION_DECL)
unused = false;
+ /* Preserve the block, it is referenced by at least the inline
+ entry point marker. */
+ else if (debug_nonbind_markers_p
+ && inlined_function_outer_scope_p (scope))
+ unused = false;
/* Innermost blocks with no live variables nor statements can be always
eliminated. */
else if (!nsubblocks)
}
else if (BLOCK_VARS (scope) || BLOCK_NUM_NONLOCALIZED_VARS (scope))
unused = false;
- /* See if this block is important for representation of inlined function.
- Inlined functions are always represented by block with
- block_ultimate_origin being set to FUNCTION_DECL and DECL_SOURCE_LOCATION
- set... */
- else if (inlined_function_outer_scope_p (scope))
+ /* See if this block is important for representation of inlined
+ function. Inlined functions are always represented by block
+ with block_ultimate_origin being set to FUNCTION_DECL and
+ DECL_SOURCE_LOCATION set, unless they expand to nothing... But
+ see above for the case of statement frontiers. */
+ else if (!debug_nonbind_markers_p
+ && inlined_function_outer_scope_p (scope))
unused = false;
else
/* Verfify that only blocks with source location set
fprintf (file, "#%i", BLOCK_NUMBER (origin));
}
}
+ if (BLOCK_FRAGMENT_ORIGIN (scope))
+ fprintf (file, " Fragment of : #%i",
+ BLOCK_NUMBER (BLOCK_FRAGMENT_ORIGIN (scope)));
+ else if (BLOCK_FRAGMENT_CHAIN (scope))
+ {
+ fprintf (file, " Fragment chain :");
+ for (t = BLOCK_FRAGMENT_CHAIN (scope); t ;
+ t = BLOCK_FRAGMENT_CHAIN (t))
+ fprintf (file, " #%i", BLOCK_NUMBER (t));
+ }
fprintf (file, " \n");
for (var = BLOCK_VARS (scope); var; var = DECL_CHAIN (var))
{
switch (kind)
{
case NOTE_INSN_BEGIN_STMT:
+ case NOTE_INSN_INLINE_ENTRY:
{
rtx_insn *note = NULL;
if (cfun->debug_nonbind_markers)
2018-02-09 Alexandre Oliva <aoliva@redhat.com>
+ * dwarf2.def (DW_AT_GNU_entry_view): New.
+
* dwarf2.def (DW_AT_GNU_locviews): New.
* dwarf2.h (enum dwarf_location_list_entry_type): Add
DW_LLE_GNU_view_pair.
See http://gcc.gnu.org/wiki/Discriminator */
DW_AT (DW_AT_GNU_discriminator, 0x2136)
DW_AT (DW_AT_GNU_locviews, 0x2137)
+DW_AT (DW_AT_GNU_entry_view, 0x2138)
/* VMS extensions. */
DW_AT (DW_AT_VMS_rtnbeg_pd_address, 0x2201)
/* GNAT extensions. */