binutils-gdb/gdb/testsuite/gdb.fortran/nested-funcs.f90
Andrew Burgess 0a4b09130a gdb/fortran: Nested subroutine support
This patch is a rebase and update of the following three patches:

   https://sourceware.org/ml/gdb-patches/2018-11/msg00298.html
   https://sourceware.org/ml/gdb-patches/2018-11/msg00302.html
   https://sourceware.org/ml/gdb-patches/2018-11/msg00301.html

I have merged these together into a single commit as the second patch,
adding scope support to nested subroutines, means that some of the
changes in the first patch are now no longer useful and would have to
be backed out.  The third patch is tightly coupled to the changes in
the second of these patches and I think deserves to live together with
it.

There is an extra change in cp-namespace.c that is new, this resolves
an issue with symbol lookup when placing breakpoints from within
nested subroutines.

There is also an extra test added to this commit 'nested-funcs-2.exp'
that was written by Richard Bunt from ARM, this offers some additional
testing of breakpoints on nested functions.

After this commit it is possible to place breakpoints on nested
Fortran subroutines and functions by using a fully scoped name, for
example, given this simple Fortran program:

    program greeting
      call message
    contains
      subroutine message
        print *, "Hello World"
      end subroutine message
    end program greeting

It is possible to place a breakpoint in 'message' with:

    (gdb) break greeting::message
    Breakpoint 1 at 0x4006c9: file basic.f90, line 5.

What doesn't work with this commit is placing a breakpoint like this:

    (gdb) break message
    Function "message" not defined.

Making this work will come in a later commit.

gdb/ChangeLog:

	* cp-namespace.c (cp_search_static_and_baseclasses): Only search
	for nested static variables when searchin VAR_DOMAIN.
	* dwarf2read.c (add_partial_symbol): Add nested subroutines to the
	global scope, update comment.
	(add_partial_subprogram): Call add_partial_subprogram recursively
	for nested subroutines when processinng Fortran.
	(load_partial_dies): Process the child entities of a subprogram
	when processing Fortran.
	(partial_die_parent_scope): Handle building scope
	for Fortran nested functions.
	(process_die): Record that nested functions have a scope.
	(new_symbol): Always record Fortran subprograms on the global
	symbol list.
	(determine_prefix): How to build the prefix for Fortran
	subprograms.

gdb/testsuite/ChangeLog:

	* gdb.fortran/nested-funcs.exp: Tests for placing breakpoints on
	nested functions.
	* gdb.fortran/nested-funcs.f90: Update expected results.
	* gdb.fortran/nested-funcs-2.exp: New file.
	* gdb.fortran/nested-funcs-2.f90: New file.

gdb/doc/ChangeLog:

	* doc/gdb.texinfo (Fortran Operators): Describe scope operator.
2019-10-03 21:25:22 +01:00

107 lines
2.9 KiB
Fortran
Executable file

! Copyright 2016-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/>.
module mod1
integer :: var_i = 1
integer :: var_const
parameter (var_const = 20)
CONTAINS
SUBROUTINE sub_nested_outer
integer :: local_int
character (len=20) :: name
name = 'sub_nested_outer_mod1'
local_int = 11
END SUBROUTINE sub_nested_outer
end module mod1
! Public sub_nested_outer
SUBROUTINE sub_nested_outer
integer :: local_int
character (len=16) :: name
name = 'sub_nested_outer external'
local_int = 11
END SUBROUTINE sub_nested_outer
! Needed indirection to call public sub_nested_outer from main
SUBROUTINE sub_nested_outer_ind
character (len=20) :: name
name = 'sub_nested_outer_ind'
CALL sub_nested_outer
END SUBROUTINE sub_nested_outer_ind
! public routine with internal subroutine
SUBROUTINE sub_with_sub_nested_outer()
integer :: local_int
character (len=16) :: name
name = 'subroutine_with_int_sub'
local_int = 1
CALL sub_nested_outer ! Should call the internal fct
CONTAINS
SUBROUTINE sub_nested_outer
integer :: local_int
local_int = 11
END SUBROUTINE sub_nested_outer
END SUBROUTINE sub_with_sub_nested_outer
! Main
program TestNestedFuncs
USE mod1, sub_nested_outer_use_mod1 => sub_nested_outer
IMPLICIT NONE
TYPE :: t_State
integer :: code
END TYPE t_State
TYPE (t_State) :: v_state
integer index, local_int
index = 13
CALL sub_nested_outer ! Call internal sub_nested_outer
CALL sub_nested_outer_ind ! Call external sub_nested_outer via sub_nested_outer_ind
CALL sub_with_sub_nested_outer ! Call external routine with nested sub_nested_outer
CALL sub_nested_outer_use_mod1 ! Call sub_nested_outer imported via module
index = 11 ! BP_main
v_state%code = 27
CONTAINS
SUBROUTINE sub_nested_outer
integer local_int
local_int = 19
v_state%code = index + local_int ! BP_outer
call sub_nested_inner
local_int = 22 ! BP_outer_2
RETURN
END SUBROUTINE sub_nested_outer
SUBROUTINE sub_nested_inner
integer local_int
local_int = 17
v_state%code = index + local_int ! BP_inner
RETURN
END SUBROUTINE sub_nested_inner
end program TestNestedFuncs