summaryrefslogtreecommitdiff
path: root/gcc/testsuite/gfortran.dg/assumed_rank_20.f90
blob: 10ad1fc8e89db038f45e3636db80d8cfde240f17 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
! { dg-do run }
!
! PR fortran/99043
!
module assumed_rank_module
    implicit none
    private

    public :: rank_of_pointer_level1
contains
    subroutine rank_of_pointer_level1(ap,aa)
        real, dimension(..), intent(in), pointer :: ap
        real, dimension(..), intent(in), allocatable :: aa
        if (rank(ap) /= 3) stop 1
        if (rank(aa) /= 3) stop 2
        call rank_of_pointer_level2(ap, aa)
    end subroutine rank_of_pointer_level1

    subroutine rank_of_pointer_level2(ap,aa)
        real, dimension(..), intent(in), pointer :: ap
        real, dimension(..), intent(in), allocatable :: aa

        if (rank(ap) /= 3) stop 3
        if (rank(aa) /= 3) stop 4
    end subroutine rank_of_pointer_level2
end module assumed_rank_module

program assumed_rank
    use :: assumed_rank_module, only : rank_of_pointer_level1
    implicit none
    real, dimension(:,:,:), pointer :: ap
    real, dimension(:,:,:), allocatable :: aa

    ap => null()
    call rank_of_pointer_level1(ap, aa)
end program assumed_rank