Skip to content

Commit 4e6cb28

Browse files
liuyunlong16bryanpkc
authored andcommitted
[DebugInfo] Fix bug in multi-entry procedures
When the compiler generates debuginfo for a procedure, it does not consider that if is an ENTRY statement, the number of arguments will increase by one. We can fix this problem by using the new number of arguments as returned by the process_ll_abi_func_ftn_mod function.
1 parent 175d66c commit 4e6cb28

File tree

4 files changed

+60
-8
lines changed

4 files changed

+60
-8
lines changed
Lines changed: 20 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,20 @@
1+
!RUN: %flang -g -S -emit-llvm %s -o - | FileCheck %s
2+
3+
!CHECK: [[N1:![0-9]+]] = distinct !DISubprogram
4+
!CHECK: !DILocalVariable(arg: 1, scope: [[N1]]
5+
!CHECK: !DILocalVariable(arg: 2, scope: [[N1]]
6+
!CHECK: !DILocalVariable(name: "a", arg: 3, scope: [[N1]]
7+
8+
module test
9+
contains
10+
subroutine sub(a)
11+
implicit none
12+
integer(kind = 4) :: m
13+
real(kind = 8), intent(inout) :: a(:,:)
14+
m = size(a, 1)
15+
entry subsub(a)
16+
m = size(a, 1) + 1
17+
entry subsub1(a)
18+
m = size(a, 1) + 2
19+
end subroutine sub
20+
end module

tools/flang2/flang2exe/cgmain.cpp

Lines changed: 18 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -275,6 +275,7 @@ typedef struct ComplexResultList_t {
275275
unsigned entries;
276276
} ComplexResultList_t;
277277
static ComplexResultList_t complexResultList;
278+
LL_ABI_Info *entry_abi;
278279

279280
/* --- static prototypes (exported prototypes belong in cgllvm.h) --- */
280281

@@ -1613,11 +1614,12 @@ schedule(void)
16131614

16141615
/* Build up the additional items/dummys needed for the master sptr if there
16151616
are entries, and call process_formal_arguments on that information. */
1616-
if (has_multiple_entries(gbl.currsub) && get_entries_argnum())
1617-
process_formal_arguments(
1618-
process_ll_abi_func_ftn_mod(current_module, get_master_sptr(), 1));
1619-
else
1617+
if (has_multiple_entries(gbl.currsub) && get_entries_argnum()) {
1618+
entry_abi = process_ll_abi_func_ftn_mod(current_module, get_master_sptr(), 1);
1619+
process_formal_arguments(entry_abi);
1620+
} else {
16201621
process_formal_arguments(llvm_info.abi_info);
1622+
}
16211623
made_return = false;
16221624

16231625
get_local_overlap_size();
@@ -14574,3 +14576,15 @@ get_parnum(SPTR sptr)
1457414576

1457514577
return 0;
1457614578
}
14579+
14580+
int
14581+
get_entry_parnum(SPTR sptr)
14582+
{
14583+
for (unsigned parnum = 1; parnum <= entry_abi->nargs; parnum++) {
14584+
if (entry_abi->arg[parnum].sptr == sptr) {
14585+
return parnum;
14586+
}
14587+
}
14588+
14589+
return 0;
14590+
}

tools/flang2/flang2exe/cgmain.h

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -303,4 +303,6 @@ void insert_llvm_dbg_value(OPERAND *load, LL_MDRef mdnode, SPTR sptr,
303303
bool pointer_scalar_need_debug_info(SPTR sptr);
304304

305305
int get_parnum(SPTR sptr);
306+
307+
int get_entry_parnum(SPTR sptr);
306308
#endif

tools/flang2/flang2exe/lldebug.cpp

Lines changed: 20 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -3253,10 +3253,15 @@ lldbg_emit_type(LL_DebugInfo *db, DTYPE dtype, SPTR sptr, int findex,
32533253
if (SCG(data_sptr) == SC_DUMMY) {
32543254
LL_MDRef type_mdnode = lldbg_emit_type(
32553255
db, __POINT_T, data_sptr, findex, false, false, false);
3256+
int parnum_lldbg = 0;
3257+
if (has_multiple_entries(gbl.currsub))
3258+
parnum_lldbg = get_entry_parnum(data_sptr);
3259+
else
3260+
parnum_lldbg = get_parnum(data_sptr);
32563261
dataloc = lldbg_create_local_variable_mdnode(
32573262
db, DW_TAG_arg_variable, db->cur_subprogram_mdnode, NULL,
32583263
file_mdnode, db->cur_subprogram_lineno,
3259-
get_parnum(data_sptr), type_mdnode,
3264+
parnum_lldbg, type_mdnode,
32603265
set_dilocalvariable_flags(data_sptr), ll_get_md_null());
32613266
lldbg_register_param_mdnode(db, dataloc, data_sptr);
32623267

@@ -3317,10 +3322,15 @@ lldbg_emit_type(LL_DebugInfo *db, DTYPE dtype, SPTR sptr, int findex,
33173322
if (SCG(datasptr) == SC_DUMMY) {
33183323
LL_MDRef type_mdnode = lldbg_emit_type(
33193324
db, __POINT_T, datasptr, findex, false, false, false);
3325+
int parnum_lldbg = 0;
3326+
if (has_multiple_entries(gbl.currsub))
3327+
parnum_lldbg = get_entry_parnum(data_sptr);
3328+
else
3329+
parnum_lldbg = get_parnum(data_sptr);
33203330
dataloc = lldbg_create_local_variable_mdnode(
33213331
db, DW_TAG_arg_variable, db->cur_subprogram_mdnode,
33223332
NULL, file_mdnode, db->cur_subprogram_lineno,
3323-
get_parnum(sptr), type_mdnode,
3333+
parnum_lldbg, type_mdnode,
33243334
set_dilocalvariable_flags(datasptr), ll_get_md_null());
33253335
lldbg_register_param_mdnode(db, dataloc, datasptr);
33263336
} else
@@ -3975,12 +3985,18 @@ lldbg_emit_param_variable(LL_DebugInfo *db, SPTR sptr, int findex, int parnum,
39753985
if ((ASSUMRANKG(sptr) || ASSUMSHPG(sptr)) && SDSCG(sptr)) {
39763986
type_mdnode = lldbg_emit_type(db, dtype, SDSCG(sptr), findex,
39773987
is_reference, true, false, sptr);
3978-
parnum = get_parnum(SDSCG(sptr));
3988+
if (has_multiple_entries(gbl.currsub))
3989+
parnum = get_entry_parnum(SDSCG(sptr));
3990+
else
3991+
parnum = get_parnum(SDSCG(sptr));
39793992
} else if (STYPEG(sptr) == ST_ARRAY &&
39803993
(ALLOCATTRG(sptr) || POINTERG(sptr)) && SDSCG(sptr)) {
39813994
type_mdnode = lldbg_emit_type(db, dtype, sptr, findex, is_reference, true,
39823995
false, MIDNUMG(sptr));
3983-
parnum = get_parnum(SDSCG(sptr));
3996+
if (has_multiple_entries(gbl.currsub))
3997+
parnum = get_entry_parnum(SDSCG(sptr));
3998+
else
3999+
parnum = get_parnum(SDSCG(sptr));
39844000
} else {
39854001
type_mdnode =
39864002
lldbg_emit_type(db, dtype, sptr, findex, is_reference, true, false);

0 commit comments

Comments
 (0)