lto: Remove random_seed from section name.
[official-gcc.git] / gcc / testsuite / gfortran.dg / assumed_rank_20.f90
blob10ad1fc8e89db038f45e3636db80d8cfde240f17
1 ! { dg-do run }
3 ! PR fortran/99043
5 module assumed_rank_module
6 implicit none
7 private
9 public :: rank_of_pointer_level1
10 contains
11 subroutine rank_of_pointer_level1(ap,aa)
12 real, dimension(..), intent(in), pointer :: ap
13 real, dimension(..), intent(in), allocatable :: aa
14 if (rank(ap) /= 3) stop 1
15 if (rank(aa) /= 3) stop 2
16 call rank_of_pointer_level2(ap, aa)
17 end subroutine rank_of_pointer_level1
19 subroutine rank_of_pointer_level2(ap,aa)
20 real, dimension(..), intent(in), pointer :: ap
21 real, dimension(..), intent(in), allocatable :: aa
23 if (rank(ap) /= 3) stop 3
24 if (rank(aa) /= 3) stop 4
25 end subroutine rank_of_pointer_level2
26 end module assumed_rank_module
28 program assumed_rank
29 use :: assumed_rank_module, only : rank_of_pointer_level1
30 implicit none
31 real, dimension(:,:,:), pointer :: ap
32 real, dimension(:,:,:), allocatable :: aa
34 ap => null()
35 call rank_of_pointer_level1(ap, aa)
36 end program assumed_rank