1 ! Copyright 2016-2022 Free Software Foundation, Inc.
3 ! This program is free software; you can redistribute it and/or modify
4 ! it under the terms of the GNU General Public License as published by
5 ! the Free Software Foundation; either version 3 of the License, or
6 ! (at your option) any later version.
8 ! This program is distributed in the hope that it will be useful,
9 ! but WITHOUT ANY WARRANTY; without even the implied warranty of
10 ! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
11 ! GNU General Public License for more details.
13 ! You should have received a copy of the GNU General Public License
14 ! along with this program. If not, see <http://www.gnu.org/licenses/>.
19 parameter (var_const
= 20)
23 SUBROUTINE sub_nested_outer
25 character (len
=20) :: name
27 name
= 'sub_nested_outer_mod1'
30 END SUBROUTINE sub_nested_outer
33 ! Public sub_nested_outer
34 SUBROUTINE sub_nested_outer
36 character (len
=16) :: name
38 name
= 'sub_nested_outer external'
40 END SUBROUTINE sub_nested_outer
42 ! Needed indirection to call public sub_nested_outer from main
43 SUBROUTINE sub_nested_outer_ind
44 character (len
=20) :: name
46 name
= 'sub_nested_outer_ind'
48 END SUBROUTINE sub_nested_outer_ind
50 ! public routine with internal subroutine
51 SUBROUTINE sub_with_sub_nested_outer()
53 character (len
=16) :: name
55 name
= 'subroutine_with_int_sub'
58 CALL sub_nested_outer
! Should call the internal fct
62 SUBROUTINE sub_nested_outer
65 END SUBROUTINE sub_nested_outer
67 END SUBROUTINE sub_with_sub_nested_outer
70 program TestNestedFuncs
71 USE mod1
, sub_nested_outer_use_mod1
=> sub_nested_outer
78 TYPE (t_State
) :: v_state
79 integer index
, local_int
82 CALL sub_nested_outer
! Call internal sub_nested_outer
83 CALL sub_nested_outer_ind
! Call external sub_nested_outer via sub_nested_outer_ind
84 CALL sub_with_sub_nested_outer
! Call external routine with nested sub_nested_outer
85 CALL sub_nested_outer_use_mod1
! Call sub_nested_outer imported via module
91 SUBROUTINE sub_nested_outer
94 v_state
%code
= index
+ local_int
! BP_outer
96 local_int
= 22 ! BP_outer_2
98 END SUBROUTINE sub_nested_outer
100 SUBROUTINE sub_nested_inner
103 v_state
%code
= index
+ local_int
! BP_inner
105 END SUBROUTINE sub_nested_inner
107 end program TestNestedFuncs