Gfortran and Intel Fortran run
module m_m
implicit none
contains
subroutine print_shape_and_rank(i)
! demonstrate select rank construct, section 2.12.2 of "The new features of Fortran 2018"
integer, intent(in) :: i(..) ! assumed rank argument
write (*,"(/,'rank = ',i0,' shape = ',*(1x,i0))") rank(i),shape(i)
select rank(i)
rank(0) ; print*,"rank 0"
rank(1) ; print*,"rank 1"
rank(2) ; print*,"rank 2"
rank default ; print*,"rank",rank(i)
end select
end subroutine print_shape_and_rank
end module m_m
program main
use m_m, only: print_shape_and_rank
implicit none
integer :: i=0,ivec(2)=0,imat(3,5)=0
call print_shape_and_rank(i)
call print_shape_and_rank(ivec)
call print_shape_and_rank(imat)
end program main
giving
rank = 0 shape =
rank 0
rank = 1 shape = 2
rank 1
rank = 2 shape = 3 5
rank 2
but not
module m_m
implicit none
interface print_rank
module procedure print_rank_0,print_rank_1,print_rank_2
end interface print_rank
contains
subroutine print_rank_0(i)
integer, intent(in) :: i
print*,"in print_rank, rank 0"
end subroutine print_rank_0
!
subroutine print_rank_1(i)
integer, intent(in) :: i(:)
print*,"in print_rank, rank 1"
end subroutine print_rank_1
!
subroutine print_rank_2(i)
integer, intent(in) :: i(:,:)
print*,"in print_rank, rank 2"
end subroutine print_rank_2
!
subroutine print_shape_and_rank(i)
! demonstrate select rank construct, section 2.12.2 of "The new features of Fortran 2018"
integer, intent(in) :: i(..) ! assumed rank argument
write (*,"(/,'rank = ',i0,' shape = ',*(1x,i0))") rank(i),shape(i)
select rank(i)
rank(0) ; print*,"rank 0"
rank(1) ; print*,"rank 1"
rank(2) ; print*,"rank 2"
rank default ; print*,"rank",rank(i)
end select
call print_rank(i)
end subroutine print_shape_and_rank
end module m_m
program main
use m_m, only: print_shape_and_rank
implicit none
integer :: i=0,ivec(2)=0,imat(3,5)=0
call print_shape_and_rank(i)
call print_shape_and_rank(ivec)
call print_shape_and_rank(imat)
end program main
Intel Fortran says
xxselect_rank.f90(32): error #8779: If the actual argument is assumed rank, the corresponding dummy argument must also be assumed rank. [I]
call print_rank(i)
----------------^
and gfortran says something similar. Allowing the subroutine called to depend on the array rank would be useful. This can already be done at compile time if the argument is not assumed rank, but it appears that it cannot be done at run time for an assumed rank array.