summaryrefslogtreecommitdiff
path: root/gdb/testsuite/gdb.fortran/oop_extend_type.f90
diff options
context:
space:
mode:
authorBernhard Heckel <bernhard.heckel@intel.com>2022-04-05 17:44:46 +0200
committerNils-Christian Kempke <nils-christian.kempke@intel.com>2022-04-08 12:17:13 +0200
commit87e10e9c288c2f6c933f235b623522c8d9a2d727 (patch)
tree5501d64f3c0e33b7079ed2f92bf0e65000ffbe02 /gdb/testsuite/gdb.fortran/oop_extend_type.f90
parent916c9be4a31d91ee0ebbb33efbf87a8e3cf13349 (diff)
downloadbinutils-gdb-87e10e9c288c2f6c933f235b623522c8d9a2d727.tar.gz
gdb/fortran: add support for accessing fields of extended types
Fortran 2003 supports type extension. This patch allows access to inherited members by using their fully qualified name as described in the Fortran standard. In doing so the patch also fixes a bug in GDB when trying to access the members of a base class in a derived class via the derived class' base class member. This patch fixes PR22497 and PR26373 on GDB side. Using the example Fortran program from PR22497 program mvce implicit none type :: my_type integer :: my_int end type my_type type, extends(my_type) :: extended_type end type extended_type type(my_type) :: foo type(extended_type) :: bar foo%my_int = 0 bar%my_int = 1 print*, foo, bar end program mvce and running this with GDB and setting a BP at 17: Before: (gdb) p bar%my_type A syntax error in expression, near `my_type'. (gdb) p bar%my_int There is no member named my_int. (gdb) p bar%my_type%my_int A syntax error in expression, near `my_type%my_int'. (gdb) p bar $1 = ( my_type = ( my_int = 1 ) ) After: (gdb) p bar%my_type $1 = ( my_int = 1 ) (gdb) p bar%my_int $2 = 1 # this line requires DW_TAG_inheritance to work (gdb) p bar%my_type%my_int $3 = 1 (gdb) p bar $4 = ( my_type = ( my_int = 1 ) ) In the above example "p bar%my_int" requires the compiler to emit information about the inheritance relationship between extended_type and my_type which gfortran and flang currently do not de. The respective issue gcc/49475 has been put as kfail. Co-authored-by: Nils-Christian Kempke <nils-christian.kempke@intel.com> Bug: https://sourceware.org/bugzilla/show_bug.cgi?id=26373 https://sourceware.org/bugzilla/show_bug.cgi?id=22497
Diffstat (limited to 'gdb/testsuite/gdb.fortran/oop_extend_type.f90')
-rwxr-xr-xgdb/testsuite/gdb.fortran/oop_extend_type.f9069
1 files changed, 69 insertions, 0 deletions
diff --git a/gdb/testsuite/gdb.fortran/oop_extend_type.f90 b/gdb/testsuite/gdb.fortran/oop_extend_type.f90
new file mode 100755
index 00000000000..dc91c45c60a
--- /dev/null
+++ b/gdb/testsuite/gdb.fortran/oop_extend_type.f90
@@ -0,0 +1,69 @@
+! Copyright 2022 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/>.
+
+! Test fortran extends feature (also for chained extends).
+module testmod
+ implicit none
+ type :: point
+ real :: coo(3)
+ end type
+
+ type, extends(point) :: waypoint
+ real :: angle
+ end type
+
+ type, extends(waypoint) :: fancywaypoint
+ logical :: is_fancy
+ end type
+end module
+
+program testprog
+ use testmod
+ implicit none
+
+ logical l
+ type(waypoint) :: wp
+ type(fancywaypoint) :: fwp
+ type(waypoint), allocatable :: wp_vla(:)
+
+ l = .FALSE.
+ allocate(wp_vla(3)) ! Before vla allocation
+
+ l = allocated(wp_vla) ! After vla allocation
+
+ wp%angle = 100.00
+ wp%coo(:) = 1.00
+ wp%coo(2) = 2.00
+
+ fwp%is_fancy = .TRUE.
+ fwp%angle = 10.00
+ fwp%coo(:) = 2.00
+ fwp%coo(1) = 1.00
+
+ wp_vla(1)%angle = 101.00
+ wp_vla(1)%coo(:) = 10.00
+ wp_vla(1)%coo(2) = 12.00
+
+ wp_vla(2)%angle = 102.00
+ wp_vla(2)%coo(:) = 20.00
+ wp_vla(2)%coo(2) = 22.00
+
+ wp_vla(3)%angle = 103.00
+ wp_vla(3)%coo(:) = 30.00
+ wp_vla(3)%coo(2) = 32.00
+
+ print *, wp, wp_vla, fwp ! After value assignment
+
+end program