Assumed rank arrays, interfaces, and module procedures

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.

As a workaround, I tried pointing to the assumed rank array, which gfortran accepts and Intel Fortran does not. For the code

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), target :: i(..) ! assumed rank argument
integer, pointer :: iscalar,ivec(:),imat(:,:)
write (*,"(/,'rank = ',i0,' shape = ',*(1x,i0))") rank(i),shape(i)
select rank(i)
   rank(0) ; print*,"rank 0" ; iscalar => i ; call print_rank(iscalar)
   rank(1) ; print*,"rank 1" ; ivec => i ; call print_rank(ivec)
   rank(2) ; print*,"rank 2" ; imat => i ; call print_rank(imat)
   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

Gfortran gives expected output but Intel Fortran says

Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.1 Build 20201112_000000
    Copyright (C) 1985-2020 Intel Corporation.  All rights reserved.

    xxxselect_rank.f90(28): error #8793: This assumed-rank variable must not appear in a designator or expression in this context.   [I]
       rank(0) ; print*,"rank 0" ; iscalar => i ; call print_rank(iscalar)
    ^
    xxxselect_rank.f90(37): error #7002: Error in opening the compiled module file.  Check INCLUDE paths.   [M_M]
    use m_m, only: print_shape_and_rank
    ----^
    xxxselect_rank.f90(40): error #6406: Conflicting attributes or multiple declaration of name.   [PRINT_SHAPE_AND_RANK]
    call print_shape_and_rank(i)
    -----^
    xxxselect_rank.f90(41): error #6406: Conflicting attributes or multiple declaration of name.   [PRINT_SHAPE_AND_RANK]
    call print_shape_and_rank(ivec)
    -----^
    xxxselect_rank.f90(42): error #6406: Conflicting attributes or multiple declaration of name.   [PRINT_SHAPE_AND_RANK]
    call print_shape_and_rank(imat)
    -----^
    xxxselect_rank.f90(37): error #6580: Name in only-list does not exist or is not accessible.   [PRINT_SHAPE_AND_RANK]
    use m_m, only: print_shape_and_rank
    ---------------^
    compilation aborted for xxxselect_rank.f90 (code 1)

Is the code conforming? Both compilers allow the assumed rank array to be copied to an allocatable array of the appropriate rank, so the following works:

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), target :: i(..) ! assumed rank argument
integer, allocatable :: iscalar,ivec(:),imat(:,:)
write (*,"(/,'rank = ',i0,' shape = ',*(1x,i0))") rank(i),shape(i)
select rank(i)
   rank(0) ; print*,"rank 0" ; iscalar = i ; call print_rank(iscalar)
   rank(1) ; print*,"rank 1" ; ivec = i ; call print_rank(ivec)
   rank(2) ; print*,"rank 2" ; imat = i ; call print_rank(imat)
   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

I believe ifort is wrong here. The standard says:

Within the block following a RANK ( scalar-int-constant-expr ) statement, the associating entity has the specified rank; the lower bound of each dimension is the result of the intrinsic function LBOUND (16.9.109) applied to the corresponding dimension of the selector, and the upper bound of each dimension is the result of the intrinsic function UBOUND (16.9.196) applied to the corresponding dimension of the selector.

The associating entity has the ALLOCATABLE, POINTER, or TARGET attribute if the selector has that attribute. The other attributes of the associating entity are described in 11.1.3.3.

I don’t know why ifort rejects the scalar case and not the other ranks, but… Please report this to Intel.