forked from Imagelibrary/binutils-gdb
Before this change resolve_dynamic_array_or_string was called for
all TYPE_CODE_ARRAY and TYPE_CODE_STRING types, but, in the end,
this function always called create_array_type_with_stride, which
creates a TYPE_CODE_ARRAY type.
Suppose we have
subroutine vla_array (arr1, arr2)
character (len=*):: arr1 (:)
character (len=5):: arr2 (:)
print *, arr1 ! break-here
print *, arr2
end subroutine vla_array
The "print arr1" and "print arr2" command at the "break-here" line
gives the following output:
(gdb) print arr1
$1 = <incomplete type>
(gdb) print arr2
$2 = ('abcde', 'abcde', 'abcde')
(gdb) ptype arr1
type = Type
End Type
(gdb) ptype arr2
type = character*5 (3)
Dwarf info using Intel® Fortran Compiler for such case contains following:
<1><fd>: Abbrev Number: 12 (DW_TAG_string_type)
<fe> DW_AT_name : (indirect string, offset: 0xd2): .str.ARR1
<102> DW_AT_string_length: 3 byte block: 97 23 8 (DW_OP_push_object_address; DW_OP_plus_uconst: 8)
After this change resolve_dynamic_array_or_string now calls
create_array_type_with_stride or create_string_type, so if the
incoming dynamic type is a TYPE_CODE_STRING then we'll get back a
TYPE_CODE_STRING type. Now gdb shows following:
(gdb) p arr1
$1 = ('abddefghij', 'abddefghij', 'abddefghij', 'abddefghij', 'abddefghij')
(gdb) p arr2
$2 = ('abcde', 'abcde', 'abcde')
(gdb) ptype arr1
type = character*10 (5)
(gdb) ptype arr2
type = character*5 (3)
In case of GFortran, compiler emits DW_TAG_structure_type for string type
arguments of the subroutine and it has only DW_AT_declaration tag. This
results in <incomplete type> in gdb. So, following issue is raised in gcc
bugzilla "https://gcc.gnu.org/bugzilla/show_bug.cgi?id=101826".
Fixing above issue introduce regression in gdb.fortran/mixed-lang-stack.exp,
i.e. the test forces the language to C/C++ and print a Fortran string value.
The string value is a dynamic type with code TYPE_CODE_STRING.
Before this commit the dynamic type resolution would always convert this to
a TYPE_CODE_ARRAY of characters, which the C value printing could handle.
But now after this commit we get a TYPE_CODE_STRING, which
neither the C value printing, or the generic value printing code can
support. And so, I've added support for TYPE_CODE_STRING to the generic
value printing, all characters of strings are printed together till the
first null character.
Lastly, in gdb.opt/fortran-string.exp and gdb.fortran/string-types.exp
tests it expects type of character array in 'character (3)' format but now
after this change we get 'character*3', so tests are updated accordingly.
Approved-By: Tom Tromey <tom@tromey.com>
46 lines
1.4 KiB
Fortran
46 lines
1.4 KiB
Fortran
! Copyright 2024 Free Software Foundation, Inc.
|
|
!
|
|
! This program is free software; you can redistribute it and/or modify
|
|
! it under the terms of the GNU General Public License as published by
|
|
! the Free Software Foundation; either version 3 of the License, or
|
|
! (at your option) any later version.
|
|
!
|
|
! This program is distributed in the hope that it will be useful,
|
|
! but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
! GNU General Public License for more details.
|
|
!
|
|
! You should have received a copy of the GNU General Public License
|
|
! along with this program. If not, see <http://www.gnu.org/licenses/>.
|
|
|
|
subroutine vla_array_func (arr_vla1, arr_vla2, arr2)
|
|
character (len=*):: arr_vla1 (:)
|
|
character (len=*):: arr_vla2
|
|
character (len=9):: arr2 (:)
|
|
|
|
print *, arr_vla1 ! arr_vla1-print
|
|
print *, arr_vla2
|
|
print *, arr2
|
|
print *, rank(arr_vla1)
|
|
end subroutine vla_array_func
|
|
|
|
program vla_array_main
|
|
interface
|
|
subroutine vla_array_func (arr_vla1, arr_vla2, arr2)
|
|
character (len=*):: arr_vla1 (:)
|
|
character (len=*):: arr_vla2
|
|
character (len=9):: arr2 (:)
|
|
end subroutine vla_array_func
|
|
end interface
|
|
character (len=9) :: arr1 (3)
|
|
character (len=6) :: arr2
|
|
character (len=12) :: arr3 (5)
|
|
|
|
arr1 = 'vlaaryvla'
|
|
arr2 = 'vlaary'
|
|
arr3 = 'vlaaryvlaary'
|
|
|
|
call vla_array_func (arr3, arr2, arr1)
|
|
|
|
end program vla_array_main
|