Skip to content

Commit

Permalink
[DebugInfo] Debug support for module array variables with pointer/all…
Browse files Browse the repository at this point in the history
…ocatable attribute
  • Loading branch information
alokkrsharma committed Dec 18, 2020
1 parent 2f5aa05 commit 335c4d2
Show file tree
Hide file tree
Showing 3 changed files with 59 additions and 9 deletions.
19 changes: 19 additions & 0 deletions test/debug_info/module_allocatable_arr.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
!RUN: %flang -gdwarf-4 -S -emit-llvm %s -o - | FileCheck %s

!CHECK-LABEL: distinct !DIGlobalVariable(name: "alc_arr"
!CHECK-SAME: type: [[TYPE:![0-9]+]]
!CHECK: [[TYPE]] = !DICompositeType(tag: DW_TAG_array_type,
!CHECK-SAME: elements: [[ELEMENTS:![0-9]+]], dataLocation: !DIExpression(DW_OP_push_object_address, DW_OP_deref), allocated: !DIExpression(DW_OP_push_object_address, DW_OP_deref)
!CHECK: [[ELEMENTS]] = !{[[ELEMENT:![0-9]+]]}
!CHECK: [[ELEMENT]] = !DISubrange(lowerBound: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 96, DW_OP_deref), upperBound: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 136, DW_OP_deref), stride: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 128, DW_OP_deref, DW_OP_push_object_address, DW_OP_plus_uconst, 40, DW_OP_deref, DW_OP_mul))

module mod_vars
integer, allocatable, dimension(:) :: alc_arr
end module

program main
use mod_vars
allocate (alc_arr(10))
alc_arr = 99
print *, alc_arr
end program
21 changes: 21 additions & 0 deletions test/debug_info/module_pointer_arr.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,21 @@
!RUN: %flang -gdwarf-4 -S -emit-llvm %s -o - | FileCheck %s

!CHECK-LABEL: distinct !DIGlobalVariable(name: "ptr_arr"
!CHECK-SAME: type: [[TYPE:![0-9]+]]
!CHECK: [[TYPE]] = !DICompositeType(tag: DW_TAG_array_type,
!CHECK-SAME: elements: [[ELEMENTS:![0-9]+]], dataLocation: !DIExpression(DW_OP_push_object_address, DW_OP_deref), associated: !DIExpression(DW_OP_push_object_address, DW_OP_deref)
!CHECK: [[ELEMENTS]] = !{[[ELEMENT:![0-9]+]]}
!CHECK: [[ELEMENT]] = !DISubrange(lowerBound: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 96, DW_OP_deref), upperBound: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 136, DW_OP_deref), stride: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 128, DW_OP_deref, DW_OP_push_object_address, DW_OP_plus_uconst, 40, DW_OP_deref, DW_OP_mul))

module mod_vars
integer, pointer, dimension(:) :: ptr_arr
end module

program main
use mod_vars
integer, target :: tgtarr(20)
tgtarr(1:20:2) = 22
tgtarr(2:20:2) = 33
ptr_arr => tgtarr(1:20:2)
print *, ptr_arr
end program
28 changes: 19 additions & 9 deletions tools/flang2/flang2exe/lldebug.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -580,11 +580,12 @@ lldbg_create_global_variable_mdnode(LL_DebugInfo *db, LL_MDRef context,
LLMD_Builder mdb2 = llmd_init(db->module);
llmd_set_class(mdb2, LL_DIGlobalVariableExpression);
llmd_add_md(mdb2, cur_mdnode);
/* Handle the Fortran allocatable array cases. Emit expression mdnode with a
* sigle argument of DW_OP_deref because of using sptr array$p instead of
* sptr array for debugging purpose.
*/
if (ftn_array_need_debug_info(sptr)) {
if (!ll_feature_debug_info_ver90(&cpu_llvm_module->ir) &&
ftn_array_need_debug_info(sptr)) {
/* Handle the Fortran allocatable array cases. Emit expression mdnode with
* a sigle argument of DW_OP_deref because of using sptr array$p instead
* of sptr array for debugging purpose.
*/
const unsigned deref = lldbg_encode_expression_arg(LL_DW_OP_deref, 0);
expr_mdnode = lldbg_emit_expression_mdnode(db, 1, deref);
} else
Expand Down Expand Up @@ -3292,10 +3293,20 @@ lldbg_emit_global_variable(LL_DebugInfo *db, SPTR sptr, ISZ_T off, int findex,
savedScopeIsGlobal = db->scope_is_global;
db->scope_is_global = true;
db->gbl_var_sptr = sptr;
type_mdnode =
lldbg_emit_type(db, DTYPEG(sptr), sptr, findex, false, false, false);
SPTR new_sptr = (SPTR)REVMIDLNKG(sptr);
get_extra_info_for_sptr(&display_name, &scope_mdnode, &type_mdnode, db, sptr);
display_name = SYMNAME(sptr);
if (ll_feature_debug_info_ver90(&cpu_llvm_module->ir) && CCSYMG(sptr) &&
new_sptr && (STYPEG(new_sptr) == ST_ARRAY) &&
(POINTERG(new_sptr) || ALLOCATTRG(new_sptr)) && SDSCG(new_sptr)) {
type_mdnode = lldbg_emit_type(db, DTYPEG(new_sptr), new_sptr, findex, false,
false, false);
display_name = SYMNAME(new_sptr);
flags = CCSYMG(new_sptr) ? DIFLAG_ARTIFICIAL : 0;
} else {
type_mdnode =
lldbg_emit_type(db, DTYPEG(sptr), sptr, findex, false, false, false);
flags = CCSYMG(sptr) ? DIFLAG_ARTIFICIAL : 0;
}
file_mdnode = ll_feature_debug_info_need_file_descriptions(&db->module->ir)
? get_filedesc_mdnode(db, findex)
: lldbg_emit_file(db, findex);
Expand All @@ -3310,7 +3321,6 @@ lldbg_emit_global_variable(LL_DebugInfo *db, SPTR sptr, ISZ_T off, int findex,
} else {
fwd = ll_get_md_null();
}
flags = CCSYMG(sptr) ? DIFLAG_ARTIFICIAL : 0;
if (!ll_feature_debug_info_ver90(&db->module->ir)) {
if (ftn_array_need_debug_info(sptr)) {
SPTR array_sptr = (SPTR)REVMIDLNKG(sptr);
Expand Down

0 comments on commit 335c4d2

Please sign in to comment.