diff options
author | Andrew Burgess <andrew.burgess@embecosm.com> | 2019-03-01 11:12:33 +0000 |
---|---|---|
committer | Andrew Burgess <andrew.burgess@embecosm.com> | 2019-06-16 00:29:35 +0100 |
commit | 584a927c5ad0d18e9995a0049066b6c503bb7482 (patch) | |
tree | e7235e42ae1098ff109a169478c77dc1ef97accd /gdb/testsuite/gdb.fortran/pointers.f90 | |
parent | 30056ea04ae3ecd828e2a06e12e6f174ae6659c9 (diff) | |
download | binutils-584a927c5ad0d18e9995a0049066b6c503bb7482.zip binutils-584a927c5ad0d18e9995a0049066b6c503bb7482.tar.gz binutils-584a927c5ad0d18e9995a0049066b6c503bb7482.tar.bz2 |
gdb/fortran: Show the type for non allocated / associated types
Show the type of not-allocated and/or not-associated types. For array
types and pointer to array types we are going to print the number of
ranks.
Consider this Fortran program:
program test
integer, allocatable :: vla (:)
logical l
allocate (vla(5:12))
l = allocated (vla)
end program test
And this GDB session with current HEAD:
(gdb) start
...
2 integer, allocatable :: vla (:)
(gdb) n
4 allocate (vla(5:12))
(gdb) ptype vla
type = <not allocated>
(gdb) p vla
$1 = <not allocated>
(gdb)
And the same session with this patch applied:
(gdb) start
...
2 integer, allocatable :: vla (:)
(gdb) n
4 allocate (vla(5:12))
(gdb) ptype vla
type = integer(kind=4), allocatable (:)
(gdb) p vla
$1 = <not allocated>
(gdb)
The type of 'vla' is now printed correctly, while the value itself
still shows as '<not allocated>'. How GDB prints the type of
associated pointers has changed in a similar way.
gdb/ChangeLog:
* f-typeprint.c (f_print_type): Don't return early for not
associated or not allocated types.
(f_type_print_varspec_suffix): Add print_rank parameter and print
ranks of array types in case they dangling.
(f_type_print_base): Add print_rank parameter.
gdb/testsuite/ChangeLog:
* gdb.fortran/pointers.f90: New file.
* gdb.fortran/print_type.exp: New file.
* gdb.fortran/vla-ptype.exp: Adapt expected results.
* gdb.fortran/vla-type.exp: Likewise.
* gdb.fortran/vla-value.exp: Likewise.
* gdb.mi/mi-vla-fortran.exp: Likewise.
Diffstat (limited to 'gdb/testsuite/gdb.fortran/pointers.f90')
-rw-r--r-- | gdb/testsuite/gdb.fortran/pointers.f90 | 80 |
1 files changed, 80 insertions, 0 deletions
diff --git a/gdb/testsuite/gdb.fortran/pointers.f90 b/gdb/testsuite/gdb.fortran/pointers.f90 new file mode 100644 index 0000000..cb7010d --- /dev/null +++ b/gdb/testsuite/gdb.fortran/pointers.f90 @@ -0,0 +1,80 @@ +! Copyright 2019 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/>. + +program pointers + + type :: two + integer, allocatable :: ivla1 (:) + integer, allocatable :: ivla2 (:, :) + end type two + + logical, target :: logv + complex, target :: comv + character, target :: charv + character (len=3), target :: chara + integer, target :: intv + integer, target, dimension (10,2) :: inta + real, target :: realv + type(two), target :: twov + + logical, pointer :: logp + complex, pointer :: comp + character, pointer :: charp + character (len=3), pointer :: charap + integer, pointer :: intp + integer, pointer, dimension (:,:) :: intap + real, pointer :: realp + type(two), pointer :: twop + + nullify (logp) + nullify (comp) + nullify (charp) + nullify (charap) + nullify (intp) + nullify (intap) + nullify (realp) + nullify (twop) + + logp => logv ! Before pointer assignment + comp => comv + charp => charv + charap => chara + intp => intv + intap => inta + realp => realv + twop => twov + + logv = associated(logp) ! Before value assignment + comv = cmplx(1,2) + charv = "a" + chara = "abc" + intv = 10 + inta(:,:) = 1 + inta(3,1) = 3 + realv = 3.14 + + allocate (twov%ivla1(3)) + allocate (twov%ivla2(2,2)) + twov%ivla1(1) = 11 + twov%ivla1(2) = 12 + twov%ivla1(3) = 13 + twov%ivla2(1,1) = 211 + twov%ivla2(2,1) = 221 + twov%ivla2(1,2) = 212 + twov%ivla2(2,2) = 222 + + intv = intv + 1 ! After value assignment + +end program pointers |