Skip to content

Commit

Permalink
[DebugInfo] Flang should generate debug location for limited instruct…
Browse files Browse the repository at this point in the history
…ions in prolog (#940)

* Flang should not generate debug location for instructions in prolog

Due to this wrong debug_line section entry is created with wrong instruction
marked as 'prologue_end'. More details in commited test cases.

* Minor modifications are done.

- to match coding style of newly added functions to rest of the file.
- to reduce optimization option to -O0 in test case.
  • Loading branch information
alokkrsharma authored Jan 13, 2021
1 parent ed3ed0d commit 2eab099
Show file tree
Hide file tree
Showing 5 changed files with 129 additions and 4 deletions.
30 changes: 30 additions & 0 deletions test/debug_info/dwarfdump_prolog.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,30 @@
!RUN: %flang -g -O0 %s -o %t
!RUN: llvm-dwarfdump --debug-line %t -o - | FileCheck %s

!CHECK: name: "dwarfdump_prolog.f90"
!CHECK: Address Line Column File ISA Discriminator Flags
!CHECK: {{0x[0-9a-f]+}} 13 1 1 0 0 is_stmt prologue_end
!CHECK: {{0x[0-9a-f]+}} 29 1 1 0 0 is_stmt prologue_end

subroutine show (message, array)
character (len=*) :: message
integer :: array(:)

print *, message
print *, array

end subroutine show

program prolog

interface
subroutine show (message, array)
character (len=*) :: message
integer :: array(:)
end subroutine show
end interface

integer :: array(10) = (/1,2,3,4,5,6,7,8,9,10/)

call show ("array", array)
end program prolog
37 changes: 37 additions & 0 deletions test/debug_info/prolog.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,37 @@
!RUN: %flang -g -S -emit-llvm %s -o - | FileCheck %s

! check non debug instructions should not have debug location
!CHECK: define void @show_
!CHECK: call void @llvm.dbg.declare
!CHECK-SAME: , !dbg {{![0-9]+}}
!CHECK-NOT: bitcast i64* %"array$sd" to i8*, !dbg
!CHECK: store i64 {{%[0-9]+}}, i64* %z_b_3_{{[0-9]+}}, align 8
!CHECK: br label
!CHECK: ret void, !dbg {{![0-9]+}}
subroutine show (message, array)
character (len=*) :: message
integer :: array(:)

print *, message
print *, array

end subroutine show

!CHECK: define void @MAIN_
!CHECK-NOT: bitcast void (...)* @fort_init to void (i8*, ...)*, !dbg {{![0-9]+}}
!CHECK: call void @llvm.dbg.declare
!CHECK-SAME: , !dbg {{![0-9]+}}
!CHECK: ret void, !dbg
program prolog

interface
subroutine show (message, array)
character (len=*) :: message
integer :: array(:)
end subroutine show
end interface

integer :: array(10) = (/1,2,3,4,5,6,7,8,9,10/)

call show ("array", array)
end program prolog
48 changes: 46 additions & 2 deletions tools/flang2/flang2exe/cgmain.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -2794,6 +2794,41 @@ write_verbose_type(LL_Type *ll_type)
print_token(ll_type->str);
}

/* whether debug location should be suppressed */
static bool
should_suppress_debug_loc(INSTR_LIST *instrs)
{
if (!instrs)
return false;

// return true if not a call instruction
switch (instrs->i_name) {
case I_INVOKE:
return false;
case I_CALL:
// f90 runtime functions fort_init and f90_* dont need debug location
if (instrs->prev && (instrs->operands->ot_type == OT_TMP) &&
(instrs->operands->tmps == instrs->prev->tmps) &&
(instrs->prev->operands->ot_type == OT_VAR)) {
// We dont need to expose those internals in prolog to user
// %1 = bitcast void (...)* @fort_init to void (i8*, ...)*
// call void (i8*, ...) %1(i8* %0)
// %8 = bitcast void (...)* @f90_template1_i8 to void (i8*, i8*, i8*, i8*,
// i8*, i8*, ...)*
// call void (i8*, i8*, i8*, i8*, i8*, i8*, ...) %8(i8*
// %2, i8* %3, i8* %4, i8* %5, i8* %6, i8* %7)

if (char *name_str = instrs->prev->operands->string) {
return (!strncmp(name_str, "@fort_init", strlen("@fort_init")) ||
!strncmp(name_str, "@f90_", strlen("@f90_")));
}
}
return false;
default:
return true;
}
}

/**
\brief Write the instruction list to the LLVM IR output file
*/
Expand Down Expand Up @@ -3328,8 +3363,17 @@ write_instructions(LL_Module *module)
ERR_Fatal);
}
}
if (!ISNVVMCODEGEN &&
(!LL_MDREF_IS_NULL(instrs->dbg_line_op) && !dbg_line_op_written)) {
/*
* Do not dump debug location here if
* - it is NULL
* - it is already written (dbg_line_op_written) or
* - it is a known internal (f90 runtime) call in prolog (fort_init &
* f90_*)
*/
if (!(LL_MDREF_IS_NULL(instrs->dbg_line_op) || dbg_line_op_written ||
((instrs->dbg_line_op ==
lldbg_get_subprogram_line(module->debug_info)) &&
should_suppress_debug_loc(instrs)))) {
print_dbg_line(instrs->dbg_line_op);
}
#if DEBUG
Expand Down
16 changes: 14 additions & 2 deletions tools/flang2/flang2exe/lldebug.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -129,6 +129,7 @@ struct LL_DebugInfo {
LL_MDRef cur_module_mdnode;
LL_MDRef cur_cmnblk_mdnode;
int cur_subprogram_lineno;
LL_MDRef cur_subprogram_line_mdnode;
LL_MDRef cur_subprogram_null_loc;
LL_MDRef cur_line_mdnode;
PARAMINFO param_stack[PARAM_STACK_SIZE];
Expand Down Expand Up @@ -2161,8 +2162,10 @@ lldbg_emit_subprogram(LL_DebugInfo *db, SPTR sptr, DTYPE ret_dtype, int findex,
db->import_entity_list->entity_type);
db->import_entity_list = db->import_entity_list->next;
}
db->cur_subprogram_null_loc =
lldbg_create_location_mdnode(db, 0, 0, db->cur_subprogram_mdnode);
db->cur_subprogram_null_loc =
lldbg_create_location_mdnode(db, 0, 0, db->cur_subprogram_mdnode);
db->cur_subprogram_lineno = lineno;
db->cur_subprogram_line_mdnode = ll_get_md_null();
db->param_idx = 0;
memset(db->param_stack, 0, sizeof(PARAMINFO) * PARAM_STACK_SIZE);
lldbg_emit_lexical_blocks(db, sptr, findex, targetNVVM);
Expand Down Expand Up @@ -2306,6 +2309,10 @@ lldbg_emit_line(LL_DebugInfo *db, int lineno)
db->cur_line_mdnode =
lldbg_create_location_mdnode(db, lineno, 1, db->blk_tab[idx].mdnode);
}
// it is not yet column aware so comparing only line
if (lineno == db->cur_subprogram_lineno)
db->cur_subprogram_line_mdnode = db->cur_line_mdnode;

last_line = lineno;
}
}
Expand Down Expand Up @@ -3529,3 +3536,8 @@ new_debug_name(const char *str1, const char *str2, const char *str3)
return (const char *)new_name;
}

LL_MDRef
lldbg_get_subprogram_line(LL_DebugInfo *db)
{
return db->cur_subprogram_line_mdnode;
}
2 changes: 2 additions & 0 deletions tools/flang2/flang2exe/lldebug.h
Original file line number Diff line number Diff line change
Expand Up @@ -273,4 +273,6 @@ void InitializeDIFlags(const LL_IRFeatures *feature);

void lldbg_reset_module(LL_DebugInfo *db);

/// \brief Get the debug location mdnode of the current procedure.
LL_MDRef lldbg_get_subprogram_line(LL_DebugInfo *db);
#endif /* LLDEBUG_H_ */

0 comments on commit 2eab099

Please sign in to comment.