The code that handled allocatable array had swapped `count` with `upperBound`. This did not get caught earlier as all the example were using 1 as `lowerBound`. Fixes #98166. With the fix in place, the GDB now correctly handles the case pointed in the bug ticket. (gdb) p min::alloc2d $2 = ((0, 0, 0) (0, 0, 0) (0, 0, 0) (0, 0, 0) (0, 0, 0)) (gdb) ptype min::alloc2d type = integer, allocatable (-1:1,-2:2)
14 lines
830 B
Fortran
14 lines
830 B
Fortran
! RUN: %flang_fc1 -emit-llvm -debug-info-kind=standalone %s -o - | FileCheck %s
|
|
|
|
subroutine ff(arr)
|
|
implicit none
|
|
integer :: arr(:, :)
|
|
return arr(1,1)
|
|
end subroutine ff
|
|
|
|
! CHECK-DAG: !DICompositeType(tag: DW_TAG_array_type{{.*}}elements: ![[ELEMS:[0-9]+]], dataLocation: !DIExpression(DW_OP_push_object_address, DW_OP_deref))
|
|
! CHECK-DAG: ![[ELEMS]] = !{![[ELEM1:[0-9]+]], ![[ELEM2:[0-9]+]]}
|
|
! CHECK-DAG: ![[ELEM1]] = !DISubrange(count: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 32, DW_OP_deref), lowerBound: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 24, DW_OP_deref))
|
|
! CHECK-DAG: ![[ELEM2]] = !DISubrange(count: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 56, DW_OP_deref), lowerBound: !DIExpression(DW_OP_push_object_address, DW_OP_plus_uconst, 48, DW_OP_deref))
|
|
|